radrow
radrow

Reputation: 7129

Lifting - generalization

I need to use heavy function lifting, eg.

k = myFunc
  <$> someFunctionName 1
  <*> someFunctionName 2
  <*> someFunctionName 3
  <*> someFunctionName 4
  <*> someFunctionName 5
  <*> someFunctionName 6
  <*> someFunctionName 8
  <*> someFunctionName 9
  -- ...

Which is not provided for bigger functions (about 20 arguments) by Prelude. Is there smart way to do such a lift without explicitly chaining those aps? I am looking for something like

k = magic (map someFunctionName [1,2,3,4,5,6,8,9]) myFunc 

I may be hard to guess the type of magic as it depends on number of arguments of lifted function. It is of course not possible to use map on list here (or is it?), I put it only as a viewpoint.

I think I am looking for something that could be nicely solved by dependent types, which are not included in Haskell, but maybe there is some tricky way to workaround it (TemplateHaskell?)

Do you have any ideas how to make it more elegant and flexible?

edit: In my case types of chained functions are all the same.

Upvotes: 2

Views: 240

Answers (1)

Li-yao Xia
Li-yao Xia

Reputation: 33389

Lift constructors

Using type classes we can define a generalized version of liftA/ap. The tricky part is to infer when to stop lifting and return the result. Here we use the fact that constructors are curried functions with as many arguments as they have fields, and the result type is not a function.

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

import Text.Read

-- apF
--   :: Applicative f
--   => (i -> f a)
--   -> (a -> a -> ... ->   x)   -- constructor type
--   -> (i -> i -> ... -> f x)   -- lifted function
class Applicative f => ApF f i a s t where
  apF :: (i -> f a) -> f s -> t

-- Recursive case
-- s ~ (a -> ...)
-- t ~ (i -> ...)
instance (a ~ a', t ~ (i -> t'), ApF f i a s' t') => ApF f i a (a' -> s') t where
  apF parseArg fconstr i = apF parseArg (fconstr <*> parseArg i)

-- Base case
-- s ~   x  -- x assumed not to be a function type (not (y -> z) for any y and z)
-- t ~ f x
instance {-# OVERLAPPABLE #-} (t ~ f x, Applicative f) => ApF f i a x t where
  apF _ fconstr = fconstr

liftF :: ApF f i a s t => (i -> f a) -> s -> t
liftF parseArg constr = apF parseArg (pure constr)

main = do
  let lookup :: Int -> Maybe Integer
      lookup i =
        case drop i [2,3,5,7,11,13] of
          [] -> Nothing
          a : _ -> Just a
  print $ liftF lookup (,,) 0 2 5

Higher-kinded records and generics

Another solution is to first parameterize records by a type function wrapping every field, so that we can put things of various other related types. Those allow us to produce and consume actual records by traversing those derived structures using Haskell Generics.

data UserF f = User
  { name :: f @@ String
  , age :: f @@ Int
  } deriving G.Generic

type User = UserF Id

Type functions are defined using the type family (@@) (HKD in the blog post linked above). The ones relevant to this answer are the identity and constant functions.

type family s @@ x
type instance Id   @@ x = x
type instance Cn a @@ x = a

data Id
data Cn (a :: *)

For example, we can gather the indices used to parse CSV, in a UserF (Cn Int):

userIxes = User { name = 0, age = 2 } :: UserF (Cn Int)

Given such a parameterized record type (p = UserF), and a record of indices (ixes :: p (Cn Int)), we can parse a CSV record (r :: [String]) with parseRec below. Here using generics-sop.

parseRec :: _
         => p (Cn Int) -> [String] -> Maybe (p Id)
parseRec ixes r =
  fmap to .
  hsequence .
  htrans (Proxy :: Proxy ParseFrom) (\(I i) -> read (r !! i)) .
  from $
  ixes

Let us break down the code bottom-up. generics-sop provides combinators to transform records in a uniform way that is like using lists. It is best to follow a proper tutorial to understand the underlying details, but for the sake of demonstration, we will imagine that the middle of the pipeline between from and to is actually transforming lists, using a dynamic type Field to type heterogeneous lists.

  • from turns a record into its heterogeneous list of fields, but since they're all Int the list is really homogeneous for now from :: p (Cn Int) -> [Int].

  • Here using (!!) and read, we get and parse each field using the given index i. htrans Proxy is basically map: (Int -> Maybe Field) -> [Int] -> [Maybe Field].

  • hsequence is basically sequence :: [Maybe Field] -> Maybe [Field].

  • to turns a list of fields into a record with compatible field types, [Field] -> p Id.

The final step is effortless:

parseUser :: Record -> Maybe User
parseUser = parseRec $ User { name = 0, age = 2 }

Upvotes: 4

Related Questions