Skip to content

Instantly share code, notes, and snippets.

@CarstenKoenig
Created August 23, 2018 12:57
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 CarstenKoenig/47dfb27e864eb96dac993e89f76a896b to your computer and use it in GitHub Desktop.
Save CarstenKoenig/47dfb27e864eb96dac993e89f76a896b to your computer and use it in GitHub Desktop.
Flatten record
module Main where
import Prelude
import Data.Symbol (class IsSymbol, SProxy(..))
import Effect (Effect)
import Effect.Console (log)
import Prim.Row as Row
import Prim.RowList (kind RowList, Nil, Cons, class RowToList)
import Record (get)
import Record.Builder (Builder)
import Record.Builder as Builder
import Type.Equality (class TypeEquals)
import Type.Row (RLProxy(..))
main :: Effect Unit
main = do
log $ show $ flatten { foo : { input : "Answer"}, bar : { input : 42 } }
flatten :: forall row rl out . RowToList row rl => Flatten rl row () out => Record row -> Record out
flatten rec = Builder.build (flattenBuilder rlp rec) {}
where
rlp = RLProxy :: RLProxy rl
class Flatten (rl :: RowList) (row :: #Type) (from :: #Type) (to :: #Type) | rl -> row from to where
flattenBuilder :: forall g . g rl -> Record row -> Builder (Record from) (Record to)
instance flattenNil :: Flatten Nil row () () where
flattenBuilder _ _ = identity
instance flattenCons ::
( IsSymbol name
, TypeEquals ty' { input :: ty }
, Row.Cons name ty from' to
, Flatten tail row from from'
, Row.Lacks name from'
, Row.Cons name { input :: ty } ig row
) => Flatten (Cons name ty' tail) row from to where
flattenBuilder _ rec = first <<< flattenBuilder tailp rec
where
first :: Builder (Record from') (Record to)
first = Builder.insert namep value
value :: ty
value = inner.input
inner :: { input :: ty }
inner = get namep rec
namep = SProxy :: SProxy name
tailp = RLProxy :: RLProxy tail
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment