Skip to content

Instantly share code, notes, and snippets.

@i-am-tom
Last active September 12, 2017 21:34
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save i-am-tom/cad0518686a9694922d07913beb3a46f to your computer and use it in GitHub Desktop.
Save i-am-tom/cad0518686a9694922d07913beb3a46f to your computer and use it in GitHub Desktop.
Discarding row labels to reduce records to "HLists" (nested tuple chains)
module Main where
import Prelude (Unit, ($), discard)
import Type.Prelude
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, logShow)
import Data.Record (get)
import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\))
import Type.Row (Cons, Nil, kind RowList)
class RowToTuple (la :: RowList) (ra :: # Type) a b | la -> a b
where rowToTupleImpl :: RLProxy la -> Record ra -> Tuple a b
instance rowToTupleEmpty
:: ( IsSymbol k
, IsSymbol l
, RowCons k a tra ra
, RowCons l b xyz ra
)
=> RowToTuple (Cons k a (Cons l b Nil)) ra a b
where
rowToTupleImpl _ rs = get (SProxy :: SProxy k) rs
/\ get (SProxy :: SProxy l) rs
instance rowToTupleNonEmpty
:: ( IsSymbol k
, RowToTuple (Cons l b (Cons m c x)) ra b bs
, RowCons k a tra ra
)
=> RowToTuple (Cons k a (Cons l b (Cons m c x))) ra a (Tuple b bs)
where
rowToTupleImpl _ row
= (get (SProxy :: SProxy k) row :: a)
/\ (rowToTupleImpl (RLProxy :: RLProxy (Cons l b (Cons m c x))) row :: Tuple b bs)
rowToTuple
:: forall la ra a as
. RowToList ra la
=> RowToTuple la ra a as
=> Record ra
-> Tuple a as
rowToTuple ra = rowToTupleImpl (RLProxy :: RLProxy la) ra
main :: Eff (console :: CONSOLE) Unit
main = do
logShow $ rowToTuple { b: false, c: 3 } -- Tuple false 3
logShow $ rowToTuple { a: 1, c: 2, b: 3 } -- Tuple 1 (Tuple 3 2)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment