可以将文章内容翻译成中文,广告屏蔽插件可能会导致该功能失效(如失效,请关闭广告屏蔽插件后再试):
问题:
I am curious if it is possible to write a function apply_nth
that takes a function, the number of a parameter, and that parameter's value and then returns a new, partially-applied function.
The feeling I get is that this is impossible due to the type system, but I can't come up with a satisfying answer. I also can't come up with a working type signature.
If the language were more loosely-typed, I imagine the code might look like this.
apply_nth f 0 x = f x
apply_nth f n x = \a -> apply_nth (f a) (n-1) x
Any ideas?
回答1:
Your feeling is correct, this isn't possible. Partial application changes the type of a function, and in which way depends on what parameter you apply. But if that parameter is indexed only at runtime with an extra argument, the compiler doesn't know what the type will be, and the compiler must typecheck everything†. Really, you would need the result to have a dependent type, but Haskell is not a dependently-typed language.
Now, actually, if you toss in a couple of GHC extensions and introduce a couple of weird type families, then you can actually achieve something similar to such a dependent type. But honestly, I doubt this is a good idea. What do you need this for anyway? If you're juggling functions with more than, say, 8 parameters, you're probably doing something wrong, and for easier functions you can just define 8 combinators, each of which applies a single, fixed argument-position.
Alternatively: a similar function that's perhaps reasonable would be
apply_nth :: ([a] -> b) -> Int -> a -> [a] -> b
apply_nth f i a xs = f $ before ++ [a] ++ after
where (before, after) = splitAt i xs
Unlike with argument-lists, a value-list can easily be hundreds of elements long, so in this case pre-applying single elements, indexed at runtime, can make sense.
†This isn't just a safety precaution – it's necessary because types don't even exist at runtime, so the compiler needs to complete prepare all conditionals that might depend on types. This is why Haskell is safe and concise and fast and extensible, like few other languages.
回答2:
Not that weird type families, but not super nice either:
{-# LANGUAGE GADTs, DataKinds, TypeFamilies, TypeOperators #-}
import Data.Proxy
type family Fun as b where
Fun '[] b = b
Fun (a ': as) b = a -> Fun as b
data SL as where
Sn :: SL '[]
Sc :: SL as -> SL (a ': as)
applyN :: Proxy c -> SL as -> Fun as (b -> c) -> b -> Fun as c
applyN p Sn f y = f y
applyN p (Sc s) f y = \x -> applyN p s (f x) y
main = print $ applyN Proxy (Sc (Sc Sn)) zipWith [1,2,3] (-) [6,5,4] -- [5,3,1]
We can also package Proxy c
into SL
:
data SL as c where
Sn :: SL '[] c
Sc :: SL as c -> SL (a ': as) c
applyN :: SL as c -> Fun as (b -> c) -> b -> Fun as c
applyN Sn f y = f y
applyN (Sc s) f y = \x -> applyN s (f x) y
main = print $ applyN (Sc (Sc Sn)) zipWith [1,2,3] (-) [6,5,4] -- [5,3,1]
Or you can simply define a few combinators:
z = id
s r f y x = r (f x) y
applyN = id
main = print $ applyN (s (s z)) zipWith [1,2,3] (-) [6,5,4] -- [5,3,1]
回答3:
Sure, with a bit of type class "magic":
{-# LANGUAGE DataKinds, KindSignatures, UndecidableInstances #-}
data Nat = Z | S Nat
data SNat (n :: Nat) where
SZ :: SNat Z
SS :: SNat n -> SNat (S n)
class ApplyNth (n :: Nat) arg fn fn' | n arg fn -> fn', n fn -> arg where
applyNth :: SNat n -> arg -> fn -> fn'
instance ApplyNth Z a (a -> b) b where
applyNth SZ a f = f a
instance ApplyNth n arg' fn fn' => ApplyNth (S n) arg' (arg0 -> fn) (arg0 -> fn') where
applyNth (SS n) a f = \a0 -> applyNth n a (f a0)
The general type for applyNth
says, it takes an index (a natural number - encoded in the type), an argument, a function, and returns a function.
Note the two functional dependencies. The first says that given the index, the argument, and the input function, the type of the output function is known. This much is obvious. The second says that that given the index and the input function, ApplyNth
is able to look inside the function and figure out what argument it needs!
This function plays pretty well with type inference:
>:t \x -> applyNth (SS SZ) x (^)
\x -> applyNth (SS SZ) x (^)
:: (Num fn', Integral b) => b -> fn' -> fn'
>:t applyNth (SS SZ) 0 (^)
applyNth (SS SZ) 0 (^) :: Num fn' => fn' -> fn'
>:t applyNth (SS SZ) (0 :: Integer) (^)
applyNth (SS SZ) (0 :: Integer) (^) :: Num fn' => fn' -> fn'
>:t applyNth (SS SZ) ('a' :: Char) (^)
<interactive>:1:32: Warning:
Could not deduce (Integral Char) arising from a use of `^'
...
applyNth (SS SZ) ('a' :: Char) (^) :: Num fn' => fn' -> fn'
>let squared = applyNth (SS SZ) 2 (^)
>:t squared
squared :: Num fn' => fn' -> fn'
>squared 3
9
>squared 100
10000
>let f a b c d e = mapM_ putStrLn
[ show n ++ ": " ++ x
| (n,x) <- zip [0..]
[show a, show b, show c, show d, show e] ]
>applyNth SZ 'q' $
applyNth (SS $ SZ) [1,8,42] $
applyNth SZ (True, 10) $
applyNth (SS $ SS $ SS SZ) "abcd" $
applyNth (SS $ SS $ SS SZ) pi $
f
0: (True,10)
1: 'q'
2: [1,8,42]
3: 3.141592653589793
4: "abcd"
You can also define it in operator form:
infixl 9 =:
(=:) :: ApplyNth n arg fn fn' => SNat n -> arg -> fn -> fn'
(=:) = applyNth
r =
SZ =: 'q' $
SS SZ =: [1,8,42] $
SZ =: (True, 10) $
(SS $ SS $ SS SZ) =: "abcd" $
(SS $ SS $ SS SZ) =: pi $
f
回答4:
Not inside of any language called "Haskell" but if you look at Glasgow Haskell, including unsafe functions, then you can partially apply in the manner you desire... well you do have to correctly specify the argument location. THIS IS A HORRIBLE HACK. Do not do this unless you are extremely comfortable with... well.. don't do this.
This code is from back when I asked a similar question (Using Typeable to partially apply function at run-time (any time types match)).
import Unsafe.Coerce
testBuild :: String
testBuild = let f = buildFunc typedFunction ("argument 'b'", 42::Int) 1
in f "Look I have applied " " and it seems to work."
typedFunction :: String -> (String,Int) -> String -> String
typedFunction = (\a b c -> a ++ show b ++ c)
buildFunc :: f -> x -> Int -> g
buildFunc f x 0 = unsafeCoerce f x
buildFunc f x i =
let res = \y -> (buildFunc (unsafeCoerce f y) x (i-1))
in unsafeCoerce res
And the output:
*Main> testBuild
"Look I have applied (\"argument 'b'\",42) and it seems to work."
Notice if we specified the argument index (1) incorrectly then the program would likely segfault.