Can <*> be folded in haskell?

I want to implement something like

fun1 f a_ziplist

      

eg

getZipList $ (\x y z -> x*y+z) <$> ZipList [4,7] <*> ZipList [6,9] <*> ZipList [5,10]

f = (\x y z -> x*y+z) 
ziplist = [[4,7],[6,9],[5,10]]

      

To do this I want to recursively apply <*> as

foldx (h:w) = h <*> foldx w
foldx (w:[]) = w

      

but it seems impossible to make it recursive.

+3


source share


5 answers


Play with the types in ghci to see where they take us.

λ import Control.Applicative

      

A type (<*>)

λ :t (<*>)
(<*>) :: Applicative f => f (a -> b) -> f a -> f b

      

Type foldr

:

λ :t Prelude.foldr
Prelude.foldr :: (a -> b -> b) -> b -> [a] -> b

      

Perhaps we could use it (<*>)

as a function that is passed as the first parameter foldr

. What will the type be?



λ :t Prelude.foldr (<*>)
Prelude.foldr (<*>) :: Applicative f => f a -> [f (a -> a)] -> f a

      

So it seems like it takes an initial value in an applicative context and a list of functions in an applicative context and returns another application.

For example, using ZipList

as an application:

λ getZipList $ Prelude.foldr (<*>) (ZipList [2,3]) [ ZipList [succ,pred], ZipList [(*2)] ]

      

Result:

[5]

      

I'm not sure if this is what this question asked, but it looks like a natural way fold

with (<*>)

.

+4


source


If the argument is ziplist

supposed to be a simple list, it looks impossible. This is because it fold f [a1,...,an]

should be well typed for everyone n

, so it f

should be a function type taking at least n

arguments for each n

, hence infinitely many.

However, if you are using the GADT list type, in which values ​​display their length as a natural level, you can achieve something similar to what you want.



{-# LANGUAGE DataKinds, KindSignatures, TypeFamilies, GADTs #-}

import Control.Applicative

-- | Type-level naturals
data Nat = Z | S Nat

-- | Type family for n-ary functions
type family   Fn (n :: Nat) a b
type instance Fn Z     a b = b
type instance Fn (S n) a b = a -> Fn n a b

-- | Lists exposing their length in their type
data List a (n :: Nat) where
  Nil :: List a Z
  Cons :: a -> List a n -> List a (S n)

-- | General <*> applied to a list of arguments of the right length
class Apply (n :: Nat) where
   foldF :: Applicative f => f (Fn n a b) -> List (f a) n -> f b

instance Apply Z where
   foldF f0 Nil = f0

instance Apply n => Apply (S n) where
   foldF fn (Cons x xs) = foldF (fn <*> x) xs

test :: [(Integer,Integer,Integer)]
test = foldF (pure (,,)) (Cons [10,11] (Cons [20,21] (Cons [30,31] Nil)))
-- Result: [(10,20,30),(10,20,31),(10,21,30),(10,21,31)
--         ,(11,20,30),(11,20,31),(11,21,30),(11,21,31)]

      

+4


source


In general, folding (<*>)

is tricky due to the types as others have mentioned. But for your specific example, where your ziplist items are of the same type, you can use a different method and do your calculation, with a slight change to f

, to force it to use a list instead of arguments:

import Data.Traversable
import Control.Applicative

f = (\[x,y,z] -> x*y+z) 
ziplist = [[4,7],[6,9],[5,10]]

fun1 f l = getZipList $ f <$> traverse ZipList l

      

This is even possible with functions Data.List

and Prelude

:

fun1 f = map f . transpose

      

+2


source


To do this I want to recursively apply <*>

like

foldx (h:w) = h <*> foldx w
foldx (w:[]) = w

      

but it seems impossible to make it recursive.

I think you are confused compared to left-right associativity. danidiaz will reformulate this in terms foldr (<*>)

, which is quite useful for this analysis. The documentation provides a useful definition foldr

in terms of extension
:

foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z) ...)

      

So, apply this to your case:

foldr (<*>) z [x1, x2, ..., xn] == x1 <*> (x2 <*> ... (xn <*> z) ...)

      

Pay attention to the parens. <*>

left-associative, so the extension foldr

differs from:

x1 <*> x2 <*> ... <*> xn <*> z == ((... (x1 <*> x2) <*> ...) <*> xn) <*> z

      


Think a little more about what it means foldr (<*>)

. Another way to think about it is to rewrite it a bit:

flip (foldr (<*>)) :: Applicative f :: [f (a -> a)] -> f a -> f a

      

The types of form (a -> a)

are often called endomorphisms , and they form a monoid, and the composition as an operation and id

as an identity. There's a newtype

wrapper in Data.Monoid

for them:

newtype Endo a = Endo { appEndo :: a -> a }

instance Monoid (Endo a) where
    mempty = id
    mappend = (.)

      

This gives us another way to think about foldr (<*>)

, phrasing it in terms of Endo

:

toEndo :: Applicative f => f (a -> a) -> Endo (f a)
toEndo ff = Endo (ff <*>)

      

And then, what foldr (<*>)

basically shrinks that monoid:

foldrStar :: Applicative f => [f (a -> a)] -> Endo (f a)
foldrStar fs = mconcat $ map toMonoid fs

      

0


source


what you have is equivalent zipWith3 (\x y z -> x*y+z) [4,7] [6,9] [5,10]

.

is not possible foldl

<*>

(and you need foldl

as it <*>

links from the left), because foldl :: (a -> b -> a) -> a -> [b] -> a

i.e. it's the samea

in a -> b -> a

, but when you apply your ternary function on the first list of numbers, you get a list of binary functions, then unary functions in the next step, and only finally numbers (all different types):

>> let xs = map ZipList [[4,7],[6,9],[5,10]]    
>> getZipList $ pure (\x y z -> x*y+z) <*> (xs!!0) <*> (xs!!1) <*> (xs!!2)
[29,73]
>> foldl (<*>) (pure (\x y z -> x*y+z)) xs

<interactive>:1:6:
    Occurs check: cannot construct the infinite type: b = a -> b
      Expected type: f (a -> b)
      Inferred type: f b
    In the first argument of `foldl', namely `(<*>)'
    In the expression: foldl (<*>) (pure (\ x y z -> x * y + z)) xs

>> :t foldl
foldl ::                   ( a         ->  b  ->  a ) -> a -> [b] -> a
>> :t (<*>)
(<*>) :: (Applicative f) => f (a -> b) -> f a -> f b    -- f (a -> b) = f b

      

Chi's answer addresses this, but arity is fixed (code-specific). In fact, this answer does define a (limited version) zipWithN

(well, when used with an applique ZipList

, obviously it works with any app at all) for anyone N

(but just for functions like a -> a -> a -> ... -> a

), whereas for example

zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> 
            [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]

      

(in other words, it zipWith3 (,,) [10,11] ([20,21]::[Integer]) ([30,31]::[Int])

works ).

0


source







All Articles