Suppose I have a large record (with 20+ fields), and I’d like to use HKD on it. But when I compile the following code, it uses up all my 8G memory before being terminated. (Compiled with GHC-9.8.2, on WSL2-Ubuntu-22.04)
module Test where
import Prelude
import GHC.Generics
import Barbies
import Barbies.Bare
import Data.Kind
data Foo t (f :: Type -> Type) = Foo
{ field01 :: Wear t f Int
, field02 :: Wear t f Int
, field03 :: Wear t f Int
, field04 :: Wear t f Int
, field05 :: Wear t f Int
, field06 :: Wear t f Int
, field07 :: Wear t f Int
, field08 :: Wear t f Int
, field09 :: Wear t f Int
, field10 :: Wear t f Int
, field11 :: Wear t f Int
, field12 :: Wear t f Int
, field13 :: Wear t f Int
, field14 :: Wear t f Int
, field15 :: Wear t f Int
, field16 :: Wear t f Int
, field17 :: Wear t f Int
, field18 :: Wear t f Int
, field19 :: Wear t f Int
, field20 :: Wear t f Int
}
deriving Generic
instance FunctorB (Foo Bare)
instance FunctorB (Foo Covered)
instance ApplicativeB (Foo Covered)
instance ConstraintsB (Foo Bare)
instance ConstraintsB (Foo Covered)
instance BareB Foo
I wonder if it is an intended behavior or a memory leak. If the former is the case, are there any alternative methods to do similar things?
Any suggestions are appreciated.