Skip to content

Commit

Permalink
Merge pull request #11 from composite-hs/df/nfdata
Browse files Browse the repository at this point in the history
NFData
  • Loading branch information
dfithian authored Dec 16, 2023
2 parents d946fb0 + 5d91528 commit 92b706c
Show file tree
Hide file tree
Showing 3 changed files with 13 additions and 6 deletions.
5 changes: 5 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,10 @@
# Changelog

## next version

* NFData instance for Record removed, since it overlapped with Vinyl's
* NFData instance for Field added

## 0.8.2.2

* No visible changes
Expand Down
8 changes: 8 additions & 0 deletions src/Composite/CoRecord.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module Composite.CoRecord where

import Prelude
import Composite.Record (AllHave, HasInstances, (:->)(getVal, Val), reifyDicts, reifyVal, val, zipRecsWith)
import Control.DeepSeq (NFData, rnf)
import Control.Lens (Prism', Wrapped, Unwrapped, prism', review, view, _Wrapped')
import Control.Monad.Except (ExceptT, throwError, withExceptT)
import Data.Functor.Contravariant (Contravariant(contramap))
Expand Down Expand Up @@ -41,6 +42,13 @@ instance forall rs. (RMap rs, RecAll Maybe rs Eq, RecApplicative rs, RecordToLis
f (Compose (Dict a)) b = Const $ a == b
toRec = reifyConstraint . fieldToRec

instance forall rs. (AllHave '[NFData] rs, RecApplicative rs) => NFData (CoRec Identity rs) where
rnf (CoVal (Identity x)) = rnf' x
where
rnfer :: Rec (Op ()) rs
rnfer = reifyDicts (Proxy @'[NFData]) (\ _ -> Op rnf)
rnf' = runOp (rget rnfer)

-- |The common case of a 'CoRec' with @f ~ 'Identity'@, i.e. a regular value.
type Field = CoRec Identity

Expand Down
6 changes: 0 additions & 6 deletions src/Composite/Record.hs
Original file line number Diff line number Diff line change
Expand Up @@ -88,12 +88,6 @@ instance Monad ((:->) s) where
instance NFData a => NFData (s :-> a) where
rnf (Val x) = rnf x

instance NFData (Record '[]) where
rnf RNil = ()

instance (NFData x, NFData (Record xs)) => NFData (Record (x : xs)) where
rnf (x :& xs) = rnf x `seq` rnf xs

instance forall (s :: Symbol) a. (KnownSymbol s, Show a) => Show (s :-> a) where
showsPrec p (Val a) = ((symbolVal (Proxy :: Proxy s) ++ " :-> ") ++) . showsPrec p a

Expand Down

0 comments on commit 92b706c

Please sign in to comment.