Open treeowl opened 3 years ago
For alens
, we generally want to perform the lookup eagerly to ensure we don't leak the argument array into the results. In the case where someone is using, e.g., set
or .~
(from lens
), this leads to an unnecessary array lookup. I can use a somewhat intricate set of rewrite rules to detect when the function argument to alens
doesn't use its argument, and avoid the lookup in that case. @acowley, do you think it's worth that extra complexity? To guide your decision, here's the code for it, approximately:
-- Turn off demand/cpr analysis, and don't expose unfoldings.
-- The values in this module must be completely opaque from
-- the outside.
{-# OPTIONS_GHC -O0 #-}
module Data.Vinyl.Internal.Bogus where
any1, any2 :: a
any1 = error "oops1"
any2 = error "oops2"
module Data.Vinyl.ARec.Internal where
[.....]
-- | Define a lens for a field of an 'ARec'.
alens :: forall f g t t' ts ts'. (Functor g, NatToInt (RIndex t ts))
=> (f t -> g (f t')) -> ARec f ts -> g (ARec f ts')
alens f (ARec arr@(Arr.Array _ _ _ arr#))
| let !i@(I# i#) = natToInt @(RIndex t ts)
, (# ft_ #) <- indexArray# arr# i#
, let ft = unsafeCoerce ft_ :: f t
= fmap (\ft' -> ARec (BArray.unsafeReplace arr [(i,unsafeCoerce ft')])) (f ft)
{-# INLINE [0] alens #-}
{-# RULES
-- Apply the function to two opaque values.
"alens/with_fakes" [~1] forall f. alens f = alens_with_fakes (f any1) (f any2) f
-- If GHC determines that f any1 = f any2, then f must ignore its argument
-- altogether.
"alens/constant" forall f x. alens_with_fakes x x f = alens_constant x f
-- Write-back rule.
"alens/without_fakes" [1] forall f a b. alens_with_fakes a b f = alens f
#-}
alens_with_fakes :: forall f g t t' ts ts'. (Functor g, NatToInt (RIndex t ts))
=> g (f t') -> g (f t') -> (f t -> g (f t')) -> ARec f ts -> g (ARec f ts')
alens_with_fakes _ _ f r = alens f r
{-# INLINE [0] alens_with_fakes #-}
-- We take the function here solely for its type information.
-- We could probably simplify this a bit.
alens_constant :: forall f g t t' ts ts' x. (Functor g, NatToInt (RIndex t ts))
=> g (f t') -> (f t -> x) -> ARec f ts -> g (ARec f ts')
alens_constant res _ (ARec arr)
| let !i = natToInt @(RIndex t ts)
= fmap (\ft' -> ARec (BArray.unsafeReplace arr [(i,unsafeCoerce ft')])) res
{-# INLINE alens_constant #-}
Currently,
ARec
is quite lazy (sometimes too lazy), whileRec
is quite strict (sometimes too strict for my taste, but that's a design decision). At the very least,alens
,arecGetSubset
, and so on should perform their lookups eagerly (usingArray
internals, or perhaps switching away fromData.Array
in favor of something easier to control). At most, all the modification functions should insert things in WHNF.