結論
Getting (First a) s aはMaybe aを返せるようなPrism' s aの特殊化だから。
(Getting (First a) s aはPrism' s a)
(^?)とは?
Prismのアクセサです。
ちょうどLensの(^.)と同じですが、PrismなのでMaybeで結果を返します。
(^?) :: s -> Getting (First a) s a -> Maybe a
このようなPrismを作った時に使います。
Test.hs
{-# LANGUAGE TemplateHaskell #-}
module Test
( Foo(..)
, _Bar
, _Baz
) where
import Control.Lens (makePrisms)
data Foo = Bar Int
| Baz Char
makePrisms ''Foo
-- 以下の関数がコンパイル時に定義される
-- _Bar :: (Choice p, Applicative f) => p Int (f Int) -> p Foo (f Foo)
-- _Baz :: (Choice p, Applicative f) => p Char (f Char) -> p Foo (f Foo)
Main.hs
import Test
import Control.Lens ((^?))
x :: Foo
x = Bar 10
y :: Foo
y = Baz 'a'
main :: IO ()
main = do
print $ x ^? _Bar
print $ x ^? _Baz
print $ y ^? _Bar
print $ y ^? _Baz
output
Just 10
Nothing
Nothing
Just 'a'
Prismはこんな型です。
type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t)
-- _Bar :: (Choice p, Applicative f) => p Int (f Int) -> p Foo (f Foo)
-- _Baz :: (Choice p, Applicative f) => p Char (f Char) -> p Foo (f Foo)
しかしPrismのアクセサである(^?)は、
Prism s t a bではなくGetting (First a) s aを要求します。
type Getting r s a = (a -> Const r a) -> s -> Const r s
結論
やはりGetter, Getting、Setter, Settingの時と同じで、Getting (First a) s aはPrism s t a bとして一般化できます。
type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t)
type Getting r s a = (a -> Const r a) -> s -> Const r s
なぜなら……
(->)はChoiceなのでpに当てはまります。
instance Choice (->)
First aはMonoidで、かつConst (First r)はApplicativeなので、
Const (First a)がfに当てはまります。
instance Monoid (First a)
instance Monoid a => Applicative (Const a)
(First aはMaybe aと同型です)
これを簡約すると
Getting (First a) s a = (a -> Const (First a) a) -> s -> Const (First a) s
(Const (First a)を一般化) ==> forall f. Applicative f => (a -> f a) -> s -> f s
((->)を一般化) ==> forall p f. (Choice p, Applicative f) => p a (f a) -> p s (f s)
= Prism s s a a
(s,aを一般化) ==> Prism s t a b
となるので、Prism s t a bはGetting (First a) s aの一般化です。
それによりGetting (First a) s aはPrism s s a aになるので、
(^?)はより特殊化された型Getting (First a) s aを受け取ります。
(特殊化することによりMaybe aを返せるようにしてるはず)
Prism s s a aはPrism' s aなので、上述の結論に帰着します。
1,2ヶ月前にlensを使い始めたときからの疑問だったのですが、わかってしまえば最強ですね。
よっしゃ ![]()