{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
#if __GLASGOW_HASKELL__ < 806
{-# LANGUAGE TypeInType #-}
#endif
{-# OPTIONS_GHC -Wno-incomplete-patterns #-}
module Data.Vinyl.SRec (
SRec(..), toSRec, fromSRec
, sget, sput, slens
, srecGetSubset, srecSetSubset
, toSRec2, fromSRec2, SRec2(..)
, FieldOffset, FieldOffsetAux(..), StorableAt(..)
, peekField, pokeField
) where
import Data.Coerce (coerce)
#if __GLASGOW_HASKELL__ < 806
import Data.Kind
#endif
import Data.Vinyl.Core
import Data.Vinyl.Functor (Lift(..), Compose(..), type (:.), ElField)
import Data.Vinyl.Lens (RecElem(..), RecSubset(..), type (⊆), RecElemFCtx)
import Data.Vinyl.TypeLevel (NatToInt, RImage, RIndex, Nat(..), RecAll, AllConstrained)
import Foreign.Marshal.Utils (copyBytes)
import Foreign.Ptr (Ptr)
import Foreign.Storable (Storable(..))
import System.IO.Unsafe (unsafePerformIO, unsafeDupablePerformIO)
#if __GLASGOW_HASKELL__ >= 900
import Unsafe.Coerce (unsafeCoerce#)
import GHC.Prim (touch#, RealWorld)
#else
import GHC.Prim (touch#, unsafeCoerce#, RealWorld)
#endif
import GHC.IO (IO(IO))
import GHC.Base (realWorld#)
import GHC.TypeLits (Symbol)
import GHC.Prim (MutableByteArray#, newAlignedPinnedByteArray#, byteArrayContents#)
import GHC.Ptr (Ptr(..))
import GHC.Types (Int(..))
data Bytes = Bytes (MutableByteArray# RealWorld)
newBytes :: Int -> IO Bytes
newBytes :: Int -> IO Bytes
newBytes (I# Int#
n) = (State# RealWorld -> (# State# RealWorld, Bytes #)) -> IO Bytes
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, Bytes #)) -> IO Bytes)
-> (State# RealWorld -> (# State# RealWorld, Bytes #)) -> IO Bytes
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case Int#
-> Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d.
Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
newAlignedPinnedByteArray# Int#
n Int#
8# State# RealWorld
s of
(# State# RealWorld
s', MutableByteArray# RealWorld
mbarr #) -> (# State# RealWorld
s', MutableByteArray# RealWorld -> Bytes
Bytes MutableByteArray# RealWorld
mbarr #)
touchBytes :: Bytes -> IO ()
touchBytes :: Bytes -> IO ()
touchBytes (Bytes MutableByteArray# RealWorld
mbarr) = (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s -> case MutableByteArray# RealWorld -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# MutableByteArray# RealWorld
mbarr State# RealWorld
s of State# RealWorld
s' -> (# State# RealWorld
s', () #)
{-# INLINE touchBytes #-}
withBytesPtr :: Bytes -> (Ptr a -> IO r) -> IO r
withBytesPtr :: Bytes -> (Ptr a -> IO r) -> IO r
withBytesPtr b :: Bytes
b@(Bytes MutableByteArray# RealWorld
mbarr) Ptr a -> IO r
f = do
Ptr a -> IO r
f (Addr# -> Ptr a
forall a. Addr# -> Ptr a
Ptr (ByteArray# -> Addr#
byteArrayContents# (MutableByteArray# RealWorld -> ByteArray#
unsafeCoerce# MutableByteArray# RealWorld
mbarr))) IO r -> IO () -> IO r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Bytes -> IO ()
touchBytes Bytes
b
{-# INLINE withBytesPtr #-}
newtype ForeignPtr (a :: k) = ForeignPtr Bytes
withForeignPtr :: ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr :: ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr (ForeignPtr Bytes
b) = Bytes -> (Ptr b -> IO r) -> IO r
forall a r. Bytes -> (Ptr a -> IO r) -> IO r
withBytesPtr Bytes
b
{-# INLINE withForeignPtr #-}
mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
mallocForeignPtrBytes = (Bytes -> ForeignPtr a) -> IO Bytes -> IO (ForeignPtr a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bytes -> ForeignPtr a
forall k (a :: k). Bytes -> ForeignPtr a
ForeignPtr (IO Bytes -> IO (ForeignPtr a))
-> (Int -> IO Bytes) -> Int -> IO (ForeignPtr a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> IO Bytes
newBytes
{-# INLINE mallocForeignPtrBytes #-}
newtype SRec2 (g :: k -> *) (f :: k -> *) (ts :: [k]) =
SRec2 (ForeignPtr (Rec f ts))
newtype SRec f ts = SRecNT { SRec f ts -> SRec2 f f ts
getSRecNT :: SRec2 f f ts }
toSRec2 :: forall f ts. Storable (Rec f ts) => Rec f ts -> SRec2 f f ts
toSRec2 :: Rec f ts -> SRec2 f f ts
toSRec2 Rec f ts
x = IO (SRec2 f f ts) -> SRec2 f f ts
forall a. IO a -> a
unsafePerformIO (IO (SRec2 f f ts) -> SRec2 f f ts)
-> IO (SRec2 f f ts) -> SRec2 f f ts
forall a b. (a -> b) -> a -> b
$ do
ForeignPtr (Rec f ts)
ptr <- Int -> IO (ForeignPtr (Rec f ts))
forall k (a :: k). Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Rec f ts -> Int
forall a. Storable a => a -> Int
sizeOf (Rec f ts
forall a. HasCallStack => a
undefined :: Rec f ts))
ForeignPtr (Rec f ts) -> SRec2 f f ts
forall k (g :: k -> *) (f :: k -> *) (ts :: [k]).
ForeignPtr (Rec f ts) -> SRec2 g f ts
SRec2 ForeignPtr (Rec f ts)
ptr SRec2 f f ts -> IO () -> IO (SRec2 f f ts)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ForeignPtr (Rec f ts) -> (Ptr (Rec f ts) -> IO ()) -> IO ()
forall k (a :: k) b r. ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr ForeignPtr (Rec f ts)
ptr ((Ptr (Rec f ts) -> Rec f ts -> IO ())
-> Rec f ts -> Ptr (Rec f ts) -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Ptr (Rec f ts) -> Rec f ts -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Rec f ts
x))
{-# NOINLINE toSRec2 #-}
toSRec :: Storable (Rec f ts) => Rec f ts -> SRec f ts
toSRec :: Rec f ts -> SRec f ts
toSRec = SRec2 f f ts -> SRec f ts
forall k (f :: k -> *) (ts :: [k]). SRec2 f f ts -> SRec f ts
SRecNT (SRec2 f f ts -> SRec f ts)
-> (Rec f ts -> SRec2 f f ts) -> Rec f ts -> SRec f ts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rec f ts -> SRec2 f f ts
forall k (f :: k -> *) (ts :: [k]).
Storable (Rec f ts) =>
Rec f ts -> SRec2 f f ts
toSRec2
{-# INLINE toSRec #-}
fromSRec2 :: Storable (Rec f ts) => SRec2 g f ts -> Rec f ts
fromSRec2 :: SRec2 g f ts -> Rec f ts
fromSRec2 (SRec2 ForeignPtr (Rec f ts)
ptr) = IO (Rec f ts) -> Rec f ts
forall a. IO a -> a
inlinePerformIO (ForeignPtr (Rec f ts)
-> (Ptr (Rec f ts) -> IO (Rec f ts)) -> IO (Rec f ts)
forall k (a :: k) b r. ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr ForeignPtr (Rec f ts)
ptr Ptr (Rec f ts) -> IO (Rec f ts)
forall a. Storable a => Ptr a -> IO a
peek)
{-# INLINE fromSRec2 #-}
fromSRec :: Storable (Rec f ts) => SRec f ts -> Rec f ts
fromSRec :: SRec f ts -> Rec f ts
fromSRec (SRecNT SRec2 f f ts
s) = SRec2 f f ts -> Rec f ts
forall u (f :: u -> *) (ts :: [u]) (g :: u -> *).
Storable (Rec f ts) =>
SRec2 g f ts -> Rec f ts
fromSRec2 SRec2 f f ts
s
{-# INLINE fromSRec #-}
{-# INLINE inlinePerformIO #-}
inlinePerformIO :: IO a -> a
inlinePerformIO :: IO a -> a
inlinePerformIO (IO State# RealWorld -> (# State# RealWorld, a #)
m) = case State# RealWorld -> (# State# RealWorld, a #)
m State# RealWorld
realWorld# of (# State# RealWorld
_, a
r #) -> a
r
data StorableAt f a where
StorableAt :: Storable (f a) => {-# UNPACK #-} !Int -> StorableAt f a
class (RIndex t ts ~ i, RecAll f ts Storable) => FieldOffsetAux f ts t i where
fieldOffset :: Int -> StorableAt f t
class FieldOffsetAux f ts t (RIndex t ts) => FieldOffset f ts t where
instance FieldOffsetAux f ts t (RIndex t ts) => FieldOffset f ts t where
instance (RecAll f (t ': ts) Storable) => FieldOffsetAux f (t ': ts) t 'Z where
fieldOffset :: Int -> StorableAt f t
fieldOffset !Int
n = Int -> StorableAt f t
forall k (f :: k -> *) (a :: k).
Storable (f a) =>
Int -> StorableAt f a
StorableAt Int
n
{-# INLINE fieldOffset #-}
instance (RIndex t (s ': ts) ~ 'S i,
FieldOffsetAux f ts t i,
RecAll f (s ': ts) Storable)
=> FieldOffsetAux f (s ': ts) t ('S i) where
fieldOffset :: Int -> StorableAt f t
fieldOffset !Int
n = Int -> StorableAt f t
forall u (f :: u -> *) (ts :: [u]) (t :: u) (i :: Nat).
FieldOffsetAux f ts t i =>
Int -> StorableAt f t
fieldOffset @f @ts @t @i (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ f s -> Int
forall a. Storable a => a -> Int
sizeOf (f s
forall a. HasCallStack => a
undefined :: f s))
{-# INLINE fieldOffset #-}
pokeField :: forall f t ts. FieldOffset f ts t
=> ForeignPtr (Rec f ts) -> f t -> IO ()
pokeField :: ForeignPtr (Rec f ts) -> f t -> IO ()
pokeField ForeignPtr (Rec f ts)
fptr f t
x = case Int -> StorableAt f t
forall u (f :: u -> *) (ts :: [u]) (t :: u) (i :: Nat).
FieldOffsetAux f ts t i =>
Int -> StorableAt f t
fieldOffset @f @ts @t Int
0 of
StorableAt Int
i -> ForeignPtr (Rec f ts) -> (Ptr Any -> IO ()) -> IO ()
forall k (a :: k) b r. ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr ForeignPtr (Rec f ts)
fptr ((Ptr Any -> IO ()) -> IO ()) -> (Ptr Any -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Any
ptr ->
Ptr Any -> Int -> f t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Any
ptr Int
i f t
x
{-# INLINE pokeField #-}
peekField :: forall f t ts. FieldOffset f ts t
=> ForeignPtr (Rec f ts) -> IO (f t)
peekField :: ForeignPtr (Rec f ts) -> IO (f t)
peekField ForeignPtr (Rec f ts)
fptr = case Int -> StorableAt f t
forall u (f :: u -> *) (ts :: [u]) (t :: u) (i :: Nat).
FieldOffsetAux f ts t i =>
Int -> StorableAt f t
fieldOffset @f @ts @t Int
0 of
StorableAt Int
i -> ForeignPtr (Rec f ts) -> (Ptr Any -> IO (f t)) -> IO (f t)
forall k (a :: k) b r. ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr ForeignPtr (Rec f ts)
fptr ((Ptr Any -> IO (f t)) -> IO (f t))
-> (Ptr Any -> IO (f t)) -> IO (f t)
forall a b. (a -> b) -> a -> b
$ \Ptr Any
ptr ->
Ptr Any -> Int -> IO (f t)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Any
ptr Int
i
{-# INLINE peekField #-}
sget :: forall f t ts. FieldOffset f ts t
=> SRec2 f f ts -> f t
sget :: SRec2 f f ts -> f t
sget (SRec2 ForeignPtr (Rec f ts)
ptr) = IO (f t) -> f t
forall a. IO a -> a
inlinePerformIO (ForeignPtr (Rec f ts) -> IO (f t)
forall u (f :: u -> *) (t :: u) (ts :: [u]).
FieldOffset f ts t =>
ForeignPtr (Rec f ts) -> IO (f t)
peekField ForeignPtr (Rec f ts)
ptr)
{-# INLINE sget #-}
mallocAndCopy :: ForeignPtr a -> Int -> IO (ForeignPtr a)
mallocAndCopy :: ForeignPtr a -> Int -> IO (ForeignPtr a)
mallocAndCopy ForeignPtr a
src Int
n = do
ForeignPtr a
dst <- Int -> IO (ForeignPtr a)
forall k (a :: k). Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
n
ForeignPtr a -> (Ptr Any -> IO (ForeignPtr a)) -> IO (ForeignPtr a)
forall k (a :: k) b r. ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr ForeignPtr a
src ((Ptr Any -> IO (ForeignPtr a)) -> IO (ForeignPtr a))
-> (Ptr Any -> IO (ForeignPtr a)) -> IO (ForeignPtr a)
forall a b. (a -> b) -> a -> b
$ \Ptr Any
src' ->
ForeignPtr a -> (Ptr Any -> IO (ForeignPtr a)) -> IO (ForeignPtr a)
forall k (a :: k) b r. ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr ForeignPtr a
dst ((Ptr Any -> IO (ForeignPtr a)) -> IO (ForeignPtr a))
-> (Ptr Any -> IO (ForeignPtr a)) -> IO (ForeignPtr a)
forall a b. (a -> b) -> a -> b
$ \Ptr Any
dst' ->
ForeignPtr a
dst ForeignPtr a -> IO () -> IO (ForeignPtr a)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Ptr Any -> Ptr Any -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes Ptr Any
dst' Ptr Any
src' Int
n
sput :: forall u (f :: u -> *) (t :: u) (ts :: [u]).
( FieldOffset f ts t
, Storable (Rec f ts)
, AllConstrained (FieldOffset f ts) ts)
=> f t -> SRec2 f f ts -> SRec2 f f ts
sput :: f t -> SRec2 f f ts -> SRec2 f f ts
sput !f t
x (SRec2 ForeignPtr (Rec f ts)
src) = IO (SRec2 f f ts) -> SRec2 f f ts
forall a. IO a -> a
unsafePerformIO (IO (SRec2 f f ts) -> SRec2 f f ts)
-> IO (SRec2 f f ts) -> SRec2 f f ts
forall a b. (a -> b) -> a -> b
$ do
let !n :: Int
n = Rec f ts -> Int
forall a. Storable a => a -> Int
sizeOf (Rec f ts
forall a. HasCallStack => a
undefined :: Rec f ts)
ForeignPtr (Rec f ts)
dst <- ForeignPtr (Rec f ts) -> Int -> IO (ForeignPtr (Rec f ts))
forall k (a :: k). ForeignPtr a -> Int -> IO (ForeignPtr a)
mallocAndCopy ForeignPtr (Rec f ts)
src Int
n
ForeignPtr (Rec f ts) -> SRec2 f f ts
forall k (g :: k -> *) (f :: k -> *) (ts :: [k]).
ForeignPtr (Rec f ts) -> SRec2 g f ts
SRec2 ForeignPtr (Rec f ts)
dst SRec2 f f ts -> IO () -> IO (SRec2 f f ts)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ForeignPtr (Rec f ts) -> f t -> IO ()
forall u (f :: u -> *) (t :: u) (ts :: [u]).
FieldOffset f ts t =>
ForeignPtr (Rec f ts) -> f t -> IO ()
pokeField ForeignPtr (Rec f ts)
dst f t
x
{-# INLINE [1] sput #-}
pokeFieldUnsafe :: forall f t ts. FieldOffset f ts t
=> f t -> SRec2 f f ts -> SRec2 f f ts
pokeFieldUnsafe :: f t -> SRec2 f f ts -> SRec2 f f ts
pokeFieldUnsafe f t
x y :: SRec2 f f ts
y@(SRec2 ForeignPtr (Rec f ts)
ptr) = IO (SRec2 f f ts) -> SRec2 f f ts
forall a. IO a -> a
unsafeDupablePerformIO (SRec2 f f ts
y SRec2 f f ts -> IO () -> IO (SRec2 f f ts)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ForeignPtr (Rec f ts) -> f t -> IO ()
forall u (f :: u -> *) (t :: u) (ts :: [u]).
FieldOffset f ts t =>
ForeignPtr (Rec f ts) -> f t -> IO ()
pokeField ForeignPtr (Rec f ts)
ptr f t
x)
{-# INLINE [1] pokeFieldUnsafe #-}
{-# RULES
"sput" forall x y z. sput x (sput y z) = pokeFieldUnsafe x (sput y z)
"sputUnsafe" forall x y z. sput x (pokeFieldUnsafe y z) = pokeFieldUnsafe x (pokeFieldUnsafe y z)
#-}
slens :: ( Functor g
, FieldOffset f ts t
, Storable (Rec f ts)
, AllConstrained (FieldOffset f ts) ts)
=> (f t -> g (f t)) -> SRec2 f f ts -> g (SRec2 f f ts)
slens :: (f t -> g (f t)) -> SRec2 f f ts -> g (SRec2 f f ts)
slens f t -> g (f t)
f SRec2 f f ts
sr = (f t -> SRec2 f f ts) -> g (f t) -> g (SRec2 f f ts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((f t -> SRec2 f f ts -> SRec2 f f ts)
-> SRec2 f f ts -> f t -> SRec2 f f ts
forall a b c. (a -> b -> c) -> b -> a -> c
flip f t -> SRec2 f f ts -> SRec2 f f ts
forall u (f :: u -> *) (t :: u) (ts :: [u]).
(FieldOffset f ts t, Storable (Rec f ts),
AllConstrained (FieldOffset f ts) ts) =>
f t -> SRec2 f f ts -> SRec2 f f ts
sput SRec2 f f ts
sr) (f t -> g (f t)
f (SRec2 f f ts -> f t
forall k (f :: k -> *) (t :: k) (ts :: [k]).
FieldOffset f ts t =>
SRec2 f f ts -> f t
sget SRec2 f f ts
sr))
{-# INLINE slens #-}
instance ( i ~ RIndex t ts
, NatToInt i
, FieldOffset ElField ts t
, Storable (Rec ElField ts)
, AllConstrained (FieldOffset ElField ts) ts)
=> RecElem (SRec2 ElField) t t ts ts i where
type RecElemFCtx (SRec2 ElField) f = f ~ ElField
rlensC :: (f t -> g (f t)) -> SRec2 ElField f ts -> g (SRec2 ElField f ts)
rlensC = (f t -> g (f t)) -> SRec2 ElField f ts -> g (SRec2 ElField f ts)
forall k (g :: * -> *) (f :: k -> *) (ts :: [k]) (t :: k).
(Functor g, FieldOffset f ts t, Storable (Rec f ts),
AllConstrained (FieldOffset f ts) ts) =>
(f t -> g (f t)) -> SRec2 f f ts -> g (SRec2 f f ts)
slens
{-# INLINE rlensC #-}
rgetC :: SRec2 ElField f ts -> f t
rgetC = SRec2 ElField f ts -> f t
forall k (f :: k -> *) (t :: k) (ts :: [k]).
FieldOffset f ts t =>
SRec2 f f ts -> f t
sget
{-# INLINE rgetC #-}
rputC :: f t -> SRec2 ElField f ts -> SRec2 ElField f ts
rputC = f t -> SRec2 ElField f ts -> SRec2 ElField f ts
forall u (f :: u -> *) (t :: u) (ts :: [u]).
(FieldOffset f ts t, Storable (Rec f ts),
AllConstrained (FieldOffset f ts) ts) =>
f t -> SRec2 f f ts -> SRec2 f f ts
sput
{-# INLINE rputC #-}
coerceSRec1to2 :: SRec f ts -> SRec2 f f ts
coerceSRec1to2 :: SRec f ts -> SRec2 f f ts
coerceSRec1to2 = SRec f ts -> SRec2 f f ts
coerce
coerceSRec2to1 :: SRec2 f f ts -> SRec f ts
coerceSRec2to1 :: SRec2 f f ts -> SRec f ts
coerceSRec2to1 = SRec2 f f ts -> SRec f ts
coerce
instance ( i ~ RIndex (t :: (Symbol,*)) (ts :: [(Symbol,*)])
, NatToInt i
, FieldOffset ElField ts t
, Storable (Rec ElField ts)
, AllConstrained (FieldOffset ElField ts) ts)
=> RecElem SRec (t :: (Symbol,*)) t (ts :: [(Symbol,*)]) ts i where
type RecElemFCtx SRec f = f ~ ElField
rlensC :: (f t -> g (f t)) -> SRec f ts -> g (SRec f ts)
rlensC f t -> g (f t)
f = (SRec2 f f ts -> SRec f ts) -> g (SRec2 f f ts) -> g (SRec f ts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SRec2 f f ts -> SRec f ts
forall k (f :: k -> *) (ts :: [k]). SRec2 f f ts -> SRec f ts
coerceSRec2to1 (g (SRec2 f f ts) -> g (SRec f ts))
-> (SRec f ts -> g (SRec2 f f ts)) -> SRec f ts -> g (SRec f ts)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (f t -> g (f t)) -> SRec2 f f ts -> g (SRec2 f f ts)
forall k (g :: * -> *) (f :: k -> *) (ts :: [k]) (t :: k).
(Functor g, FieldOffset f ts t, Storable (Rec f ts),
AllConstrained (FieldOffset f ts) ts) =>
(f t -> g (f t)) -> SRec2 f f ts -> g (SRec2 f f ts)
slens f t -> g (f t)
f (SRec2 f f ts -> g (SRec2 f f ts))
-> (SRec f ts -> SRec2 f f ts) -> SRec f ts -> g (SRec2 f f ts)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SRec f ts -> SRec2 f f ts
forall k (f :: k -> *) (ts :: [k]). SRec f ts -> SRec2 f f ts
coerceSRec1to2
{-# INLINE rlensC #-}
rgetC :: SRec f ts -> f t
rgetC = SRec2 f f ts -> f t
forall k (f :: k -> *) (t :: k) (ts :: [k]).
FieldOffset f ts t =>
SRec2 f f ts -> f t
sget (SRec2 f f ts -> f t)
-> (SRec f ts -> SRec2 f f ts) -> SRec f ts -> f t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SRec f ts -> SRec2 f f ts
forall k (f :: k -> *) (ts :: [k]). SRec f ts -> SRec2 f f ts
coerceSRec1to2
{-# INLINE rgetC #-}
rputC :: f t -> SRec f ts -> SRec f ts
rputC f t
x = SRec2 f f ts -> SRec f ts
forall k (f :: k -> *) (ts :: [k]). SRec2 f f ts -> SRec f ts
coerceSRec2to1 (SRec2 f f ts -> SRec f ts)
-> (SRec f ts -> SRec2 f f ts) -> SRec f ts -> SRec f ts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f t -> SRec2 f f ts -> SRec2 f f ts
forall u (f :: u -> *) (t :: u) (ts :: [u]).
(FieldOffset f ts t, Storable (Rec f ts),
AllConstrained (FieldOffset f ts) ts) =>
f t -> SRec2 f f ts -> SRec2 f f ts
sput f t
x (SRec2 f f ts -> SRec2 f f ts)
-> (SRec f ts -> SRec2 f f ts) -> SRec f ts -> SRec2 f f ts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SRec f ts -> SRec2 f f ts
forall k (f :: k -> *) (ts :: [k]). SRec f ts -> SRec2 f f ts
coerceSRec1to2
{-# INLINE rputC #-}
srecGetSubset :: forall u (ss :: [u]) (rs :: [u]) (f :: u -> *).
(RPureConstrained (FieldOffset f ss) rs,
RPureConstrained (FieldOffset f rs) rs,
RFoldMap rs, RMap rs, RApply rs,
Storable (Rec f rs))
=> SRec2 f f ss -> SRec2 f f rs
srecGetSubset :: SRec2 f f ss -> SRec2 f f rs
srecGetSubset (SRec2 ForeignPtr (Rec f ss)
ptr) = IO (SRec2 f f rs) -> SRec2 f f rs
forall a. IO a -> a
unsafeDupablePerformIO (IO (SRec2 f f rs) -> SRec2 f f rs)
-> IO (SRec2 f f rs) -> SRec2 f f rs
forall a b. (a -> b) -> a -> b
$ do
ForeignPtr (Rec f rs)
dst <- Int -> IO (ForeignPtr (Rec f rs))
forall k (a :: k). Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Rec f rs -> Int
forall a. Storable a => a -> Int
sizeOf (Rec f rs
forall a. HasCallStack => a
undefined :: Rec f rs))
ForeignPtr (Rec f rs) -> SRec2 f f rs
forall k (g :: k -> *) (f :: k -> *) (ts :: [k]).
ForeignPtr (Rec f ts) -> SRec2 g f ts
SRec2 ForeignPtr (Rec f rs)
dst SRec2 f f rs -> IO () -> IO (SRec2 f f rs)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ForeignPtr (Rec f rs) -> (Ptr (Rec f rs) -> IO ()) -> IO ()
forall k (a :: k) b r. ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr ForeignPtr (Rec f rs)
dst ((Ptr (Rec f rs) -> IO ()) -> IO ())
-> (Ptr (Rec f rs) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr (Rec f rs)
dst' ->
(forall (x :: u). TaggedIO x -> IO ()) -> Rec TaggedIO rs -> IO ()
forall u (rs :: [u]) m (f :: u -> *).
(Monoid m, RFoldMap rs) =>
(forall (x :: u). f x -> m) -> Rec f rs -> m
rfoldMap @rs forall (x :: u). TaggedIO x -> IO ()
forall k (a :: k). TaggedIO a -> IO ()
unTagIO (Ptr (Rec f rs) -> Rec TaggedIO rs
peekSmallPokeBig Ptr (Rec f rs)
dst'))
where peekers :: Rec (IO :. f) rs
peekers :: Rec (IO :. f) rs
peekers = (forall (a :: u). FieldOffset f ss a => (:.) IO f a)
-> Rec (IO :. f) rs
forall u (c :: u -> Constraint) (ts :: [u]) (f :: u -> *).
RPureConstrained c ts =>
(forall (a :: u). c a => f a) -> Rec f ts
rpureConstrained @(FieldOffset f ss) forall (a :: u). FieldOffset f ss a => (:.) IO f a
mkPeeker
{-# INLINE peekers #-}
mkPeeker :: FieldOffset f ss t => (IO :. f) t
mkPeeker :: (:.) IO f t
mkPeeker = IO (f t) -> (:.) IO f t
forall l k (f :: l -> *) (g :: k -> l) (x :: k).
f (g x) -> Compose f g x
Compose (ForeignPtr (Rec f ss) -> IO (f t)
forall u (f :: u -> *) (t :: u) (ts :: [u]).
FieldOffset f ts t =>
ForeignPtr (Rec f ts) -> IO (f t)
peekField ForeignPtr (Rec f ss)
ptr)
{-# INLINE mkPeeker #-}
pokers :: Ptr (Rec f rs) -> Rec (Poker f) rs
pokers :: Ptr (Rec f rs) -> Rec (Poker f) rs
pokers Ptr (Rec f rs)
dst = (forall (a :: u). FieldOffset f rs a => Poker f a)
-> Rec (Poker f) rs
forall u (c :: u -> Constraint) (ts :: [u]) (f :: u -> *).
RPureConstrained c ts =>
(forall (a :: u). c a => f a) -> Rec f ts
rpureConstrained @(FieldOffset f rs) (Ptr (Rec f rs) -> FieldOffset f rs a => Poker f a
forall (t :: u). Ptr (Rec f rs) -> FieldOffset f rs t => Poker f t
mkPoker Ptr (Rec f rs)
dst)
{-# INLINE pokers #-}
mkPoker :: forall t. Ptr (Rec f rs) -> FieldOffset f rs t => Poker f t
mkPoker :: Ptr (Rec f rs) -> FieldOffset f rs t => Poker f t
mkPoker Ptr (Rec f rs)
dst = case Int -> StorableAt f t
forall u (f :: u -> *) (ts :: [u]) (t :: u) (i :: Nat).
FieldOffsetAux f ts t i =>
Int -> StorableAt f t
fieldOffset @f @rs @t Int
0 of
StorableAt Int
i -> (f t -> TaggedIO t) -> Poker f t
forall l l' k (op :: l -> l' -> *) (f :: k -> l) (g :: k -> l')
(x :: k).
op (f x) (g x) -> Lift op f g x
Lift (IO () -> TaggedIO t
forall k (a :: k). IO () -> TaggedIO a
TaggedIO (IO () -> TaggedIO t) -> (f t -> IO ()) -> f t -> TaggedIO t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (Rec f rs) -> Int -> f t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr (Rec f rs)
dst Int
i)
{-# INLINE mkPoker #-}
peekNPoke :: (IO :. f) t -> Poker f t -> TaggedIO t
peekNPoke :: (:.) IO f t -> Poker f t -> TaggedIO t
peekNPoke (Compose IO (f t)
m) (Lift f t -> TaggedIO t
f) = IO () -> TaggedIO t
forall k (a :: k). IO () -> TaggedIO a
TaggedIO (IO (f t)
m IO (f t) -> (f t -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= TaggedIO t -> IO ()
forall k (a :: k). TaggedIO a -> IO ()
unTagIO (TaggedIO t -> IO ()) -> (f t -> TaggedIO t) -> f t -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f t -> TaggedIO t
f)
{-# INLINE peekNPoke #-}
peekSmallPokeBig :: Ptr (Rec f rs) -> Rec TaggedIO rs
peekSmallPokeBig :: Ptr (Rec f rs) -> Rec TaggedIO rs
peekSmallPokeBig Ptr (Rec f rs)
dst' = (Lift (->) f TaggedIO x -> TaggedIO x)
-> Lift (->) (Poker f) TaggedIO x
forall l l' k (op :: l -> l' -> *) (f :: k -> l) (g :: k -> l')
(x :: k).
op (f x) (g x) -> Lift op f g x
Lift ((Lift (->) f TaggedIO x -> TaggedIO x)
-> Lift (->) (Poker f) TaggedIO x)
-> ((:.) IO f x -> Lift (->) f TaggedIO x -> TaggedIO x)
-> (:.) IO f x
-> Lift (->) (Poker f) TaggedIO x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.) IO f x -> Lift (->) f TaggedIO x -> TaggedIO x
forall (t :: u). (:.) IO f t -> Poker f t -> TaggedIO t
peekNPoke (forall (x :: u). (:.) IO f x -> Lift (->) (Poker f) TaggedIO x)
-> Rec (IO :. f) rs -> Rec (Lift (->) (Poker f) TaggedIO) rs
forall u (rs :: [u]) (f :: u -> *) (g :: u -> *).
RMap rs =>
(forall (x :: u). f x -> g x) -> Rec f rs -> Rec g rs
<<$>> Rec (IO :. f) rs
peekers Rec (Lift (->) (Poker f) TaggedIO) rs
-> Rec (Poker f) rs -> Rec TaggedIO rs
forall u (rs :: [u]) (f :: u -> *) (g :: u -> *).
RApply rs =>
Rec (Lift (->) f g) rs -> Rec f rs -> Rec g rs
<<*>> Ptr (Rec f rs) -> Rec (Poker f) rs
pokers Ptr (Rec f rs)
dst'
{-# INLINE srecGetSubset #-}
newtype TaggedIO a = TaggedIO { TaggedIO a -> IO ()
unTagIO :: IO () }
type Poker f = Lift (->) f TaggedIO
srecSetSubset :: forall u (f :: u -> *) (ss :: [u]) (rs :: [u]).
(rs ⊆ ss,
RPureConstrained (FieldOffset f ss) rs,
RPureConstrained (FieldOffset f rs) rs,
RFoldMap rs, RMap rs, RApply rs,
Storable (Rec f ss))
=> SRec2 f f ss -> SRec2 f f rs -> SRec2 f f ss
srecSetSubset :: SRec2 f f ss -> SRec2 f f rs -> SRec2 f f ss
srecSetSubset (SRec2 ForeignPtr (Rec f ss)
srcBig) (SRec2 ForeignPtr (Rec f rs)
srcSmall) = IO (SRec2 f f ss) -> SRec2 f f ss
forall a. IO a -> a
unsafeDupablePerformIO (IO (SRec2 f f ss) -> SRec2 f f ss)
-> IO (SRec2 f f ss) -> SRec2 f f ss
forall a b. (a -> b) -> a -> b
$ do
let n :: Int
n = Rec f ss -> Int
forall a. Storable a => a -> Int
sizeOf (Rec f ss
forall a. HasCallStack => a
undefined :: Rec f ss)
ForeignPtr (Rec f ss)
dst <- Int -> IO (ForeignPtr (Rec f ss))
forall k (a :: k). Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
n
ForeignPtr (Rec f ss) -> (Ptr Any -> IO ()) -> IO ()
forall k (a :: k) b r. ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr ForeignPtr (Rec f ss)
srcBig ((Ptr Any -> IO ()) -> IO ()) -> (Ptr Any -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Any
srcBig' ->
ForeignPtr (Rec f ss) -> (Ptr Any -> IO ()) -> IO ()
forall k (a :: k) b r. ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr ForeignPtr (Rec f ss)
dst ((Ptr Any -> IO ()) -> IO ()) -> (Ptr Any -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Any
dst' ->
Ptr Any -> Ptr Any -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes Ptr Any
dst' Ptr Any
srcBig' Int
n
ForeignPtr (Rec f ss) -> SRec2 f f ss
forall k (g :: k -> *) (f :: k -> *) (ts :: [k]).
ForeignPtr (Rec f ts) -> SRec2 g f ts
SRec2 ForeignPtr (Rec f ss)
dst SRec2 f f ss -> IO () -> IO (SRec2 f f ss)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ForeignPtr (Rec f ss) -> (Ptr (Rec f ss) -> IO ()) -> IO ()
forall k (a :: k) b r. ForeignPtr a -> (Ptr b -> IO r) -> IO r
withForeignPtr ForeignPtr (Rec f ss)
dst ((Ptr (Rec f ss) -> IO ()) -> IO ())
-> (Ptr (Rec f ss) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr (Rec f ss)
dst' ->
(forall (x :: u). TaggedIO x -> IO ()) -> Rec TaggedIO rs -> IO ()
forall u (rs :: [u]) m (f :: u -> *).
(Monoid m, RFoldMap rs) =>
(forall (x :: u). f x -> m) -> Rec f rs -> m
rfoldMap @rs forall (x :: u). TaggedIO x -> IO ()
forall k (a :: k). TaggedIO a -> IO ()
unTagIO
((Lift (->) f TaggedIO x -> TaggedIO x)
-> Lift (->) (Lift (->) f TaggedIO) TaggedIO x
forall l l' k (op :: l -> l' -> *) (f :: k -> l) (g :: k -> l')
(x :: k).
op (f x) (g x) -> Lift op f g x
Lift ((Lift (->) f TaggedIO x -> TaggedIO x)
-> Lift (->) (Lift (->) f TaggedIO) TaggedIO x)
-> ((:.) IO f x -> Lift (->) f TaggedIO x -> TaggedIO x)
-> (:.) IO f x
-> Lift (->) (Lift (->) f TaggedIO) TaggedIO x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.) IO f x -> Lift (->) f TaggedIO x -> TaggedIO x
forall (t :: u). (:.) IO f t -> Poker f t -> TaggedIO t
peekNPoke (forall (x :: u).
(:.) IO f x -> Lift (->) (Lift (->) f TaggedIO) TaggedIO x)
-> Rec (IO :. f) rs
-> Rec (Lift (->) (Lift (->) f TaggedIO) TaggedIO) rs
forall u (rs :: [u]) (f :: u -> *) (g :: u -> *).
RMap rs =>
(forall (x :: u). f x -> g x) -> Rec f rs -> Rec g rs
<<$>> Rec (IO :. f) rs
peekers Rec (Lift (->) (Lift (->) f TaggedIO) TaggedIO) rs
-> Rec (Lift (->) f TaggedIO) rs -> Rec TaggedIO rs
forall u (rs :: [u]) (f :: u -> *) (g :: u -> *).
RApply rs =>
Rec (Lift (->) f g) rs -> Rec f rs -> Rec g rs
<<*>> Ptr (Rec f ss) -> Rec (Lift (->) f TaggedIO) rs
pokers Ptr (Rec f ss)
dst'))
where peekers :: Rec (IO :. f) rs
peekers :: Rec (IO :. f) rs
peekers = (forall (a :: u). FieldOffset f rs a => (:.) IO f a)
-> Rec (IO :. f) rs
forall u (c :: u -> Constraint) (ts :: [u]) (f :: u -> *).
RPureConstrained c ts =>
(forall (a :: u). c a => f a) -> Rec f ts
rpureConstrained @(FieldOffset f rs) forall (a :: u). FieldOffset f rs a => (:.) IO f a
mkPeeker
{-# INLINE peekers #-}
mkPeeker :: FieldOffset f rs t => (IO :. f) t
mkPeeker :: (:.) IO f t
mkPeeker = IO (f t) -> (:.) IO f t
forall l k (f :: l -> *) (g :: k -> l) (x :: k).
f (g x) -> Compose f g x
Compose (ForeignPtr (Rec f rs) -> IO (f t)
forall u (f :: u -> *) (t :: u) (ts :: [u]).
FieldOffset f ts t =>
ForeignPtr (Rec f ts) -> IO (f t)
peekField ForeignPtr (Rec f rs)
srcSmall)
pokers :: Ptr (Rec f ss) -> Rec (Poker f) rs
pokers :: Ptr (Rec f ss) -> Rec (Lift (->) f TaggedIO) rs
pokers Ptr (Rec f ss)
dst = (forall (a :: u). FieldOffset f ss a => Poker f a)
-> Rec (Lift (->) f TaggedIO) rs
forall u (c :: u -> Constraint) (ts :: [u]) (f :: u -> *).
RPureConstrained c ts =>
(forall (a :: u). c a => f a) -> Rec f ts
rpureConstrained @(FieldOffset f ss) (Ptr (Rec f ss) -> Poker f a
forall (t :: u). FieldOffset f ss t => Ptr (Rec f ss) -> Poker f t
mkPoker Ptr (Rec f ss)
dst)
{-# INLINE pokers #-}
mkPoker :: forall t. FieldOffset f ss t => Ptr (Rec f ss) -> Poker f t
mkPoker :: Ptr (Rec f ss) -> Poker f t
mkPoker Ptr (Rec f ss)
dst = case Int -> StorableAt f t
forall u (f :: u -> *) (ts :: [u]) (t :: u) (i :: Nat).
FieldOffsetAux f ts t i =>
Int -> StorableAt f t
fieldOffset @f @ss @t Int
0 of
StorableAt Int
i -> (f t -> TaggedIO t) -> Poker f t
forall l l' k (op :: l -> l' -> *) (f :: k -> l) (g :: k -> l')
(x :: k).
op (f x) (g x) -> Lift op f g x
Lift (IO () -> TaggedIO t
forall k (a :: k). IO () -> TaggedIO a
TaggedIO (IO () -> TaggedIO t) -> (f t -> IO ()) -> f t -> TaggedIO t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (Rec f ss) -> Int -> f t -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr (Rec f ss)
dst Int
i)
{-# INLINE mkPoker #-}
peekNPoke :: (IO :. f) t -> Poker f t -> TaggedIO t
peekNPoke :: (:.) IO f t -> Poker f t -> TaggedIO t
peekNPoke (Compose IO (f t)
m) (Lift f t -> TaggedIO t
f) = IO () -> TaggedIO t
forall k (a :: k). IO () -> TaggedIO a
TaggedIO (IO (f t)
m IO (f t) -> (f t -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= TaggedIO t -> IO ()
forall k (a :: k). TaggedIO a -> IO ()
unTagIO (TaggedIO t -> IO ()) -> (f t -> TaggedIO t) -> f t -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f t -> TaggedIO t
f)
{-# INLINE peekNPoke #-}
{-# INLINE srecSetSubset #-}
instance (is ~ RImage rs ss,
RecSubset Rec rs ss is,
Storable (Rec ElField rs),
Storable (Rec ElField ss),
RPureConstrained (FieldOffset ElField ss) rs,
RPureConstrained (FieldOffset ElField rs) rs,
RFoldMap rs, RMap rs, RApply rs)
=> RecSubset (SRec2 ElField) rs ss is where
type RecSubsetFCtx (SRec2 ElField) f = f ~ ElField
rsubsetC :: forall g. Functor g
=> (SRec2 ElField ElField rs -> g (SRec2 ElField ElField rs))
-> SRec2 ElField ElField ss
-> g (SRec2 ElField ElField ss)
rsubsetC :: (SRec2 ElField ElField rs -> g (SRec2 ElField ElField rs))
-> SRec2 ElField ElField ss -> g (SRec2 ElField ElField ss)
rsubsetC SRec2 ElField ElField rs -> g (SRec2 ElField ElField rs)
f big :: SRec2 ElField ElField ss
big@(SRec2 ForeignPtr (Rec ElField ss)
_) = (SRec2 ElField ElField rs -> SRec2 ElField ElField ss)
-> g (SRec2 ElField ElField rs) -> g (SRec2 ElField ElField ss)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (SRec2 ElField ElField ss
-> SRec2 ElField ElField rs -> SRec2 ElField ElField ss
forall u (f :: u -> *) (ss :: [u]) (rs :: [u]).
(rs ⊆ ss, RPureConstrained (FieldOffset f ss) rs,
RPureConstrained (FieldOffset f rs) rs, RFoldMap rs, RMap rs,
RApply rs, Storable (Rec f ss)) =>
SRec2 f f ss -> SRec2 f f rs -> SRec2 f f ss
srecSetSubset SRec2 ElField ElField ss
big) (SRec2 ElField ElField rs -> g (SRec2 ElField ElField rs)
f SRec2 ElField ElField rs
smallRec)
where smallRec :: SRec2 ElField ElField rs
smallRec :: SRec2 ElField ElField rs
smallRec = SRec2 ElField ElField ss -> SRec2 ElField ElField rs
forall u (ss :: [u]) (rs :: [u]) (f :: u -> *).
(RPureConstrained (FieldOffset f ss) rs,
RPureConstrained (FieldOffset f rs) rs, RFoldMap rs, RMap rs,
RApply rs, Storable (Rec f rs)) =>
SRec2 f f ss -> SRec2 f f rs
srecGetSubset SRec2 ElField ElField ss
big
{-# INLINE smallRec #-}
{-# INLINE rsubsetC #-}
instance (is ~ RImage rs ss,
RecSubset Rec rs ss is,
Storable (Rec ElField rs),
Storable (Rec ElField ss),
RPureConstrained (FieldOffset ElField ss) rs,
RPureConstrained (FieldOffset ElField rs) rs,
RFoldMap rs, RMap rs, RApply rs)
=> RecSubset SRec rs ss is where
type RecSubsetFCtx SRec f = f ~ ElField
rsubsetC :: (SRec f rs -> g (SRec f rs)) -> SRec f ss -> g (SRec f ss)
rsubsetC SRec f rs -> g (SRec f rs)
f (SRecNT SRec2 f f ss
s) = SRec2 f f ss -> SRec f ss
forall k (f :: k -> *) (ts :: [k]). SRec2 f f ts -> SRec f ts
SRecNT (SRec2 f f ss -> SRec f ss) -> g (SRec2 f f ss) -> g (SRec f ss)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SRec2 f f rs -> g (SRec2 f f rs))
-> SRec2 f f ss -> g (SRec2 f f ss)
forall k k (record :: (k -> *) -> [k] -> *) (rs :: [k]) (ss :: [k])
(is :: [Nat]) (g :: * -> *) (f :: k -> *).
(RecSubset record rs ss is, Functor g, RecSubsetFCtx record f) =>
(record f rs -> g (record f rs)) -> record f ss -> g (record f ss)
rsubsetC ((SRec f rs -> SRec2 f f rs) -> g (SRec f rs) -> g (SRec2 f f rs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SRec f rs -> SRec2 f f rs
forall k (f :: k -> *) (ts :: [k]). SRec f ts -> SRec2 f f ts
getSRecNT (g (SRec f rs) -> g (SRec2 f f rs))
-> (SRec2 f f rs -> g (SRec f rs))
-> SRec2 f f rs
-> g (SRec2 f f rs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SRec f rs -> g (SRec f rs)
f (SRec f rs -> g (SRec f rs))
-> (SRec2 f f rs -> SRec f rs) -> SRec2 f f rs -> g (SRec f rs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SRec2 f f rs -> SRec f rs
forall k (f :: k -> *) (ts :: [k]). SRec2 f f ts -> SRec f ts
SRecNT) SRec2 f f ss
s
{-# INLINE rsubsetC #-}