{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Capnp.Fields
( HasField (..),
Field (..),
FieldLoc (..),
DataFieldLoc (..),
FieldKind (..),
HasUnion (..),
Variant (..),
HasVariant (..),
)
where
import Capnp.Bits
import qualified Capnp.Classes as C
import qualified Capnp.Message as M
import qualified Capnp.Repr as R
import qualified Capnp.Untyped as U
import Data.Word
import GHC.OverloadedLabels (IsLabel (..))
import GHC.TypeLits (Symbol)
data FieldKind
=
Slot
|
Group
deriving (Int -> FieldKind -> ShowS
[FieldKind] -> ShowS
FieldKind -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FieldKind] -> ShowS
$cshowList :: [FieldKind] -> ShowS
show :: FieldKind -> String
$cshow :: FieldKind -> String
showsPrec :: Int -> FieldKind -> ShowS
$cshowsPrec :: Int -> FieldKind -> ShowS
Show, ReadPrec [FieldKind]
ReadPrec FieldKind
Int -> ReadS FieldKind
ReadS [FieldKind]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldKind]
$creadListPrec :: ReadPrec [FieldKind]
readPrec :: ReadPrec FieldKind
$creadPrec :: ReadPrec FieldKind
readList :: ReadS [FieldKind]
$creadList :: ReadS [FieldKind]
readsPrec :: Int -> ReadS FieldKind
$creadsPrec :: Int -> ReadS FieldKind
Read, FieldKind -> FieldKind -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldKind -> FieldKind -> Bool
$c/= :: FieldKind -> FieldKind -> Bool
== :: FieldKind -> FieldKind -> Bool
$c== :: FieldKind -> FieldKind -> Bool
Eq)
newtype Field (k :: FieldKind) a b = Field (FieldLoc k (R.ReprFor b))
data FieldLoc (k :: FieldKind) (r :: R.Repr) where
GroupField :: FieldLoc 'Group ('R.Ptr ('Just 'R.Struct))
PtrField :: R.IsPtrRepr a => Word16 -> FieldLoc 'Slot ('R.Ptr a)
DataField :: C.IsWord (R.UntypedData a) => DataFieldLoc a -> FieldLoc 'Slot ('R.Data a)
VoidField :: FieldLoc 'Slot ('R.Data 'R.Sz0)
data DataFieldLoc (sz :: R.DataSz) = DataFieldLoc
{ forall (sz :: DataSz). DataFieldLoc sz -> BitCount
shift :: !BitCount,
forall (sz :: DataSz). DataFieldLoc sz -> Word16
index :: !Word16,
forall (sz :: DataSz). DataFieldLoc sz -> Word64
mask :: !Word64,
forall (sz :: DataSz). DataFieldLoc sz -> Word64
defaultValue :: !Word64
}
class R.IsStruct a => HasUnion a where
unionField :: Field 'Slot a Word16
data Which a
data RawWhich a (mut :: M.Mutability)
internalWhich :: U.ReadCtx m mut => Word16 -> R.Raw a mut -> m (RawWhich a mut)
type instance R.ReprFor (Which a) = 'R.Ptr ('Just 'R.Struct)
instance (C.Allocate a, HasUnion a, R.IsStruct (Which a)) => C.Allocate (Which a) where
type AllocHint (Which a) = C.AllocHint a
new :: forall (m :: * -> *) s.
RWCtx m s =>
AllocHint (Which a)
-> Message ('Mut s) -> m (Raw (Which a) ('Mut s))
new AllocHint (Which a)
hint Message ('Mut s)
msg = do
R.Raw Unwrapped (Untyped (ReprFor a) ('Mut s))
struct <- forall a (m :: * -> *) s.
(Allocate a, RWCtx m s) =>
AllocHint a -> Message ('Mut s) -> m (Raw a ('Mut s))
C.new @a AllocHint (Which a)
hint Message ('Mut s)
msg
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a (mut :: Mutability).
Unwrapped (Untyped (ReprFor a) mut) -> Raw a mut
R.Raw Unwrapped (Untyped (ReprFor a) ('Mut s))
struct)
instance
( C.Allocate (Which a),
C.AllocHint (Which a) ~ (),
C.Parse (Which a) p
) =>
C.EstimateAlloc (Which a) p
data Variant (k :: FieldKind) a b = Variant
{ forall (k :: FieldKind) a b. Variant k a b -> Field k a b
field :: !(Field k a b),
forall (k :: FieldKind) a b. Variant k a b -> Word16
tagValue :: !Word16
}
class R.IsStruct a => HasField (name :: Symbol) k a b | a name -> k b where
fieldByLabel :: Field k a b
instance HasField name k a b => IsLabel name (Field k a b) where
fromLabel :: Field k a b
fromLabel = forall (name :: Symbol) (k :: FieldKind) a b.
HasField name k a b =>
Field k a b
fieldByLabel @name @k @a @b
class HasUnion a => HasVariant (name :: Symbol) k a b | a name -> k b where
variantByLabel :: Variant k a b
instance HasVariant name k a b => IsLabel name (Variant k a b) where
fromLabel :: Variant k a b
fromLabel = forall (name :: Symbol) (k :: FieldKind) a b.
HasVariant name k a b =>
Variant k a b
variantByLabel @name @k @a @b