Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Given a record of functions, and a record of data of the types acted on by the functions, how to generically apply the function record?

Tags:

haskell

The title is slightly inaccurate as my particular case is a bit more involved: rather than the functions in the first record acting directly on values in the second record, they act on a list (or other traversable) of the values. The result of an application for a particular field returns a value of the same type as was in the field, we can assume, if that buys us anything.

An example would be something like:

data Foo = Foo {
  v1 :: Int
, v2 :: Double
}

data FooFuns = FooFuns {
  v1 :: [Int] -> Int
, v2 :: [Double] -> Double
}

So the goal now is to automatically construct e.g.

result = Foo {
  v1 = (v1 FooFuns) (v1 <$> listOfFoos)
, v2 = (v2 FooFuns) (v2 <$> listOfFoos)
}

Currently I'm wrapping up the function on a list of values as a newtype (so it can be used by Higgledy's HKD) and a GADT for the Traversable constraint, but this latter part may be unnecessary, or perhaps better modeled as a typeclass:

data TraversableFun a t where
  TraversableFun :: Traversable t => (t a -> a) -> TraversableFun t a
newtype ListFun a = ListFun {unTravFun :: TraversableFun [] a}

type RecSummaryFuns a = HKD a ListFun

Now RecSummaryFuns a should have the same "field names" (constructor arguments) as a. Ideally there would be a way to easily apply sFuns to recs below to get a single record out.

applyStatFuns :: Traversable t => RecSummaryFuns r -> t r -> r
applyStatFuns sFuns recs = ???

I'm also curious if this is the best way to model the situation: basically I'm applying summary statistics to values held in records, but I need a way to encapsulate those summary statistics for each type of record.

like image 497
bbarker Avatar asked Nov 16 '19 10:11

bbarker


1 Answers

Now RecSummaryFuns a should have the same "field names" (constructor arguments) as a

This answer uses red-black-record to construct "generalized records" that have the same field names as the original Foo record. First we must auto-derive some supporting typeclasses:

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-partial-type-signatures #-} -- hide some scary types

import Data.RBR (FromRecord (..), Record, ToRecord (..), fromNP, insert, toNP, unit)
import Data.SOP (I (I), NP) -- from sop-core
import Data.SOP.NP (liftA2_NP, liftA_NP) --   useful functions for n-ary products
import GHC.Generics

data Foo
  = Foo
      { v1 :: Int,
        v2 :: Double
      }
  deriving (Show, Generic, FromRecord, ToRecord)

Now we can define a value of our generalized record, whose fields will hold functions. Sadly, we can't employ the usual record syntax:

newtype Func a = Func ([a] -> a) -- helper newtype encapsulating the function

type FooFunc = Record Func (RecordCode Foo) -- wrap every field in Func

exampleFunc :: FooFunc
exampleFunc =
      insert @"v1" (Func head) -- field names give with TypeApplications
    . insert @"v2" (Func last) -- same order as in the original record
    $ unit -- unit is the empty record

The next step is defining this generic apply function with the help of the n-ary product datatype provided by sop-core:

applyFunc ::  _ => Record Func _ -> [r] -> r
applyFunc func foos =
  let foos_NP :: [NP I _] -- a list of n-ary products. I is an identity functor
      foos_NP = toNP . toRecord <$> foos
      listfoos_NP :: [NP [] _] -- turn every component into a singleton list
      listfoos_NP = liftA_NP (\(I x) -> [x]) <$> foos_NP
      listfoo_NP :: NP [] _ -- a single n-ary product where each component is a list
      listfoo_NP = mconcat listfoos_NP
      func_NP :: NP Func _ -- turn the function record into a n-ary prod
      func_NP = toNP func
      resultFoo_NP_I :: NP I _ -- apply the functions to each list component
      resultFoo_NP_I = liftA2_NP (\(Func f) vs -> I (f vs)) func_NP listfoo_NP
   in fromRecord . fromNP $ resultFoo_NP_I -- go back to the nominal record Foo

Putting it all together:

main :: IO ()
main =
  print $
    applyFunc exampleFunc [Foo 0 0.0, Foo 1 1.0]
-- result: Foo {v1 = 0, v2 = 1.0}

Possible disadvantages of this solution are longer compilation times, and also the fact that turning the list-of-Foos into a Foo-with-list-fields inside applyFunc might be inefficient for long lists.

We could ditch red-black-record—we are only using it to preserve field names in the generalized records—and rely on sop-core / generics-sop directly; in that case field names would be handled differently—or we could simply rely on positional matching.

like image 161
danidiaz Avatar answered Sep 30 '22 17:09

danidiaz