@@ -657,11 +657,13 @@ instance (ToJSON a) => ToJSON [a] where
657657instance OVERLAPPABLE_ (GToJSON enc arity a ) => GToJSON enc arity (M1 i c a ) where
658658 -- Meta-information, which is not handled elsewhere, is ignored:
659659 gToJSON opts targs = gToJSON opts targs . unM1
660+ {-# INLINE gToJSON #-}
660661
661662instance GToJSON enc One Par1 where
662663 -- Direct occurrences of the last type parameter are encoded with the
663664 -- function passed in as an argument:
664665 gToJSON _opts (To1Args tj _) = tj . unPar1
666+ {-# INLINE gToJSON #-}
665667
666668instance ( ConsToJSON enc arity a
667669 , AllNullary (C1 c a ) allNullary
@@ -674,11 +676,13 @@ instance ( ConsToJSON enc arity a
674676 . sumToJSON opts targs
675677 . unM1
676678 | otherwise = consToJSON opts targs . unM1 . unM1
679+ {-# INLINE gToJSON #-}
677680
678681instance (ConsToJSON enc arity a ) => GToJSON enc arity (C1 c a ) where
679682 -- Constructors need to be encoded differently depending on whether they're
680683 -- a record or not. This distinction is made by 'consToJSON':
681684 gToJSON opts targs = consToJSON opts targs . unM1
685+ {-# INLINE gToJSON #-}
682686
683687instance ( AllNullary (a :+: b ) allNullary
684688 , SumToJSON enc arity (a :+: b ) allNullary
@@ -689,6 +693,7 @@ instance ( AllNullary (a :+: b) allNullary
689693 -- strings. This distinction is made by 'sumToJSON':
690694 gToJSON opts targs = (unTagged :: Tagged allNullary enc -> enc )
691695 . sumToJSON opts targs
696+ {-# INLINE gToJSON #-}
692697
693698--------------------------------------------------------------------------------
694699-- Generic toJSON
@@ -700,15 +705,18 @@ instance ( AllNullary (a :+: b) allNullary
700705instance ToJSON a => GToJSON Value arity (K1 i a ) where
701706 -- Constant values are encoded using their ToJSON instance:
702707 gToJSON _opts _ = toJSON . unK1
708+ {-# INLINE gToJSON #-}
703709
704710instance ToJSON1 f => GToJSON Value One (Rec1 f ) where
705711 -- Recursive occurrences of the last type parameter are encoded using their
706712 -- ToJSON1 instance:
707713 gToJSON _opts (To1Args tj tjl) = liftToJSON tj tjl . unRec1
714+ {-# INLINE gToJSON #-}
708715
709716instance GToJSON Value arity U1 where
710717 -- Empty constructors are encoded to an empty array:
711718 gToJSON _opts _ _ = emptyArray
719+ {-# INLINE gToJSON #-}
712720
713721instance ( WriteProduct arity a , WriteProduct arity b
714722 , ProductSize a , ProductSize b
@@ -725,6 +733,7 @@ instance ( WriteProduct arity a, WriteProduct arity b
725733 where
726734 lenProduct = (unTagged2 :: Tagged2 (a :*: b ) Int -> Int )
727735 productSize
736+ {-# INLINE gToJSON #-}
728737
729738instance ( ToJSON1 f
730739 , GToJSON Value One g
@@ -736,22 +745,26 @@ instance ( ToJSON1 f
736745 gToJSON opts targs =
737746 let gtj = gToJSON opts targs in
738747 liftToJSON gtj (listValue gtj) . unComp1
748+ {-# INLINE gToJSON #-}
739749
740750--------------------------------------------------------------------------------
741751-- Generic toEncoding
742752
743753instance ToJSON a => GToJSON Encoding arity (K1 i a ) where
744754 -- Constant values are encoded using their ToJSON instance:
745755 gToJSON _opts _ = toEncoding . unK1
756+ {-# INLINE gToJSON #-}
746757
747758instance ToJSON1 f => GToJSON Encoding One (Rec1 f ) where
748759 -- Recursive occurrences of the last type parameter are encoded using their
749760 -- ToEncoding1 instance:
750761 gToJSON _opts (To1Args te tel) = liftToEncoding te tel . unRec1
762+ {-# INLINE gToJSON #-}
751763
752764instance GToJSON Encoding arity U1 where
753765 -- Empty constructors are encoded to an empty array:
754766 gToJSON _opts _ _ = E. emptyArray_
767+ {-# INLINE gToJSON #-}
755768
756769instance ( EncodeProduct arity a
757770 , EncodeProduct arity b
@@ -761,6 +774,7 @@ instance ( EncodeProduct arity a
761774 -- the same size as the product and write the product's elements to it using
762775 -- 'encodeProduct':
763776 gToJSON opts targs p = E. list E. retagEncoding [encodeProduct opts targs p]
777+ {-# INLINE gToJSON #-}
764778
765779instance ( ToJSON1 f
766780 , GToJSON Encoding One g
@@ -772,6 +786,7 @@ instance ( ToJSON1 f
772786 gToJSON opts targs =
773787 let gte = gToJSON opts targs in
774788 liftToEncoding gte (listEncoding gte) . unComp1
789+ {-# INLINE gToJSON #-}
775790
776791--------------------------------------------------------------------------------
777792
@@ -983,6 +998,7 @@ instance ( RecordToPairs enc pairs arity f
983998 ) => ConsToJSON' enc arity f True
984999 where
9851000 consToJSON' opts targs = Tagged . fromPairs . recordToPairs opts targs
1001+ {-# INLINE consToJSON' #-}
9861002
9871003instance GToJSON enc arity f => ConsToJSON' enc arity f False where
9881004 consToJSON' opts targs = Tagged . gToJSON opts targs
@@ -1074,10 +1090,12 @@ instance ( WriteProduct arity a
10741090 lenL = len `unsafeShiftR` 1
10751091 lenR = len - lenL
10761092 ixR = ix + lenL
1093+ {-# INLINE writeProduct #-}
10771094
10781095instance OVERLAPPABLE_ (GToJSON Value arity a ) => WriteProduct arity a where
10791096 writeProduct opts targs mv ix _ =
10801097 VM. unsafeWrite mv ix . gToJSON opts targs
1098+ {-# INLINE writeProduct #-}
10811099
10821100--------------------------------------------------------------------------------
10831101
@@ -1095,9 +1113,11 @@ instance ( EncodeProduct arity a
10951113 encodeProduct opts targs (a :*: b) =
10961114 encodeProduct opts targs a >*<
10971115 encodeProduct opts targs b
1116+ {-# INLINE encodeProduct #-}
10981117
10991118instance OVERLAPPABLE_ (GToJSON Encoding arity a ) => EncodeProduct arity a where
11001119 encodeProduct opts targs a = E. retagEncoding $ gToJSON opts targs a
1120+ {-# INLINE encodeProduct #-}
11011121
11021122--------------------------------------------------------------------------------
11031123
0 commit comments