GithubHelp home page GithubHelp logo

conferopensource / composite Goto Github PK

View Code? Open in Web Editor NEW
44.0 8.0 8.0 376 KB

Integrations with Vinyl/Frames records.

License: BSD 3-Clause "New" or "Revised" License

Haskell 94.87% Makefile 0.19% Nix 4.86% Shell 0.08%
haskell haskell-library vinyl opaleye aeson

composite's Introduction

⚠️ This project has moved to https://github.com/composite-hs.

composite

Build Status

Composite is a group of libraries focusing on practical uses of composite records, in particular Vinyl, such as querying records from a database and converting them to JSON. These libraries are based on the excellent Frames style use of Vinyl records, though composite implements its own derived from Frames to make for a smaller dependency graph, as Frames is a full CSV parsing/printing and data manipulation library.

composite-aeson

composite-aeson provides JSON formatting facilities for records. JSON formats can be derived automatically when default formats are available, explicitly assembled, combined, or a mix. Aeson's use of FromJSON/ToJSON type classes is mostly avoided to make using JSON formats first-class while still convenient.

Example:

{-# LANGUAGE DataKinds, OverloadedStrings, PatternSynonyms, TypeOperators #-}
import qualified Data.Aeson as Aeson
import Composite.Aeson (JsonFormat, defaultJsonFormatRecord, recordJsonFormat, toJsonWithFormat)
import Composite.Record (Record, Rec(RNil), (:->), pattern (:*:))
import Data.Text (Text)

type FId   = "id"   :-> Int
type FName = "name" :-> Text
type User = '[FId, FName]

userFormat :: JsonFormat e (Record User)
userFormat = recordJsonFormat defaultJsonFormatRecord

alice :: Record User
alice = 1 :*: "Alice" :*: RNil

aliceJson :: Aeson.Value
aliceJson = toJsonWithFormat userFormat alice

composite-aeson-path

composite-aeson support for the path library.

composite-aeson-refined

composite-aeson support for the refined library.

composite-base

Definitions shared by the other composite libraries or generally useful when using Vinyl records. Includes some Template Haskell splices to generate various optics for records, as well as a specialization of MonadReader which works on a context record, providing general environment for a computation.

composite-binary

Instance of Binary from the binary library for composite records.

composite-ekg

Autoconfiguration of EKG from a record of EKG metrics.

composite-hashable

Instance of Hashable from the hashable library for composite records.

composite-opaleye

composite-opaleye provides the necessary instances to use a Vinyl record with the opaleye library, letting you use records for query expressions as well as result rows.

Example:

{-# LANGUAGE Arrows, DataKinds, FlexibleContexts, OverloadedStrings, PatternSynonyms, TemplateHaskell, TypeOperators #-}
import Control.Arrow (returnA)
import Composite.Opaleye (defaultRecTable)
import Composite.Record (Record, (:->))
import Composite.TH (withLensesAndProxies)
import Control.Lens (view)
import Data.Int (Int64)
import Data.Proxy (Proxy(Proxy))
import Data.Text (Text)
import Opaleye (Column, PGInt8, PGText, Query, Table(Table), (./=), asc, constant, orderBy, queryTable, restrict)

-- For each field type defined with, withLensesAndProxies will expand to the type, a record lens for the type,
-- and a proxy for the type, so for example FId is the type, fId is a lens which accesses the "id" field of any
-- record which contains that field, and fId_ is a proxy for the field type in case it's needed.
withLensesAndProxies [d|
  type FId   = "id"   :-> Int64
  type CId   = "id"   :-> Column PGInt8
  type FName = "name" :-> Text
  type CName = "name" :-> Column PGText
  |]

type User     = '[FId, FName]
type UserCols = '[CId, CName]

userTable :: Table (Record UserCols) (Record UserCols)
userTable = Table "users" defaultRecTable

userQuery :: Query (Record UserCols)
userQuery =
  orderBy (asc $ view cName) $ proc () -> do
    user <- queryTable userTable -< ()
    let recId = view cId user
    restrict -< recId ./= constant (1 :: Int64)
    returnA -< user

composite-swagger

Automatic derivation of Swagger 2 (ala swagger2) definitions for composite records.

Related work

  • compdoc provides functionality for reading a Pandoc into a record.
  • composite-dhall provides ToDhall and FromDhall instances for composite records.
  • composite-tuple provides utility functions for treating composite records as tuples, ala Relude.Extra.Tuple from relude.
  • fcf-composite provides integration with first-class-families for type-level computation of records.
  • polysemy-methodology-composite provides functions for using polysemy-methodology with composite.

example

A small servant based server which uses composite-opaleye to pull records from the database, reshape the record to an API type, and send the records out to the client as JSON via composite-aeson.

Maturity

As of writing, we use these libraries in all our Haskell projects internally and have had no major issues. There are spots using either composite or vinyl where the compiler error messages could use improvement. There are certain use cases that can cause the simplifier to crash, though we have not observed any runtime errors as yet. They have not been proven out for performance at larger scale. We'd appreciate any fixes, improvements, or experience reports.

Contributing

Contributions and feedback welcome! File an issue or make a PR.

composite's People

Contributors

asariley avatar dfithian avatar dridus avatar jkachmar avatar joshforman avatar locallycompact avatar martyall avatar zyla avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

composite's Issues

Aeson formatting data for path.

I use these definitions for the path library. https://hackage.haskell.org/package/path. Can they go somewhere?

relFileJsonFormat :: JsonFormat e (Path Rel File)
relFileJsonFormat = aesonJsonFormat

relDirJsonFormat :: JsonFormat e (Path Rel Dir)
relDirJsonFormat = aesonJsonFormat

absFileJsonFormat :: JsonFormat e (Path Abs File)
absFileJsonFormat = aesonJsonFormat

absDirJsonFormat :: JsonFormat e (Path Abs Dir)
absDirJsonFormat = aesonJsonFormat

how to do left joins properly?

I feel like it should be possible to do something like the following:

type DBUserCols = '[CUserId, CUsername]

userTable :: Table (Record DBUserCols) (Record DBUserCols)
userTable = Table "user" defaultRecTable

type DBAddressCols = '[CUserId, CCity, CStreet]
type DBMaybeAddressCols = '[Nullable CUserId, Nullable CCity, Nullable CStreet]

addressTable :: Table (Record DBUserCols) (Record DBUserCols)
addressTable = Table "user" defaultRecTable
 
usersWithAddressQ :: Query (Record DBUserCols, DBMaybeUserAddress)
usersWithAddressQ =
  let joiner l r = (l , allToNullable r)
       joinerL = (l, null)
       matcher l r  = l ^. cUserId .== r ^. cUserId
  in leftJoinF joiner joinerL matcher (queryTable userTable) (queryTable addressTable)

Is this already possible and I just haven't done it correctly? I don't see anything like the allToNullable above.

Shared entity definitions? (GHC + GHCJS)

I'm trying out this library - in combination with Opaleye and Refurb, as a replacement for the incredibly slow compile times of Beam - and I'm curious as to what pattern you used for entity definitions that are shared between backend and frontend. Seeing that you have composite-reflex and composite-aeson, I doubt that you redefined entities separately between frontend and backend.

Out of the two options that I see - ifdef'd Column definitions, and mirrored definitions in separate files (Entity and Entity.Db conditionally compiled?) - neither seems ideal, it seems all too easy to introduce errors by e.g. omitting changes in either database- or user-space definitions. I guess another option would be to stub out Opaleye.Column and Opaleye.PGTypes for GHCJS, which would allow keeping the visual assurance of F* and C* beneath each other and sounds like the best option - create an opaleye-stub for GHCJS the same way there is a ghcjs-base-stub for GHC...

But if there is a tried solution that worked well for you, I'm eager to hear it.

Edit: To clarify, having e.g. FEntityId and CEntityId (and the May variants), as well as EntityWrite + EntityWriteCols right next to each other seems ideal ergonomically. But GHCJS cannot compile opaleye nor opaleye-composite due to Package ‘postgresql-9.6.15’ is not supported on ‘js-ghcjs’, refusing to evaluate.. And so I can either split the definitions into files or spearate ifdef'd blocks (thereby remove the ergonomic advantage), or create an opaleye stub, duplicating what seems like a quite large class hierarchy - which won't actually ever be used on the frontend, as only the non-Column entities will ever be transmitted from client to server and back...

`enumJsonFormat` works on datatypes with non-nullary constructors

And this means it'll enumerate many more possible values then it should:

Composite.Aeson VitalPrelude ABE> data Foo2 = Foo | Bar Word8 deriving (Eq, Ord, Generic, Show)
Composite.Aeson VitalPrelude ABE> let ejf2 = enumJsonFormat "" :: JsonFormat () Foo2
Composite.Aeson VitalPrelude ABE> ABE.parseValue (fromJsonWithFormat ejf2) (Data.Aeson.String "Foox")
Left (BadSchema [] (FromAeson "expected one of Foo, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar,
 Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar,
Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, B
ar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Ba
r, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar
, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar,
 Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar,
Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, Bar, B
ar, not Foox"))

Maintenance

I'm sorry for opening an issue for asking a question. However, are there any future prospects of maintaining this library for newer versions of GHC? As of now, I'm unable to compile this with GHC 8.6.*.

Any updates will be helpful.

Convenience tuple functions.

These mirror some of the tuple functions in relude. http://hackage.haskell.org/package/relude-0.7.0.0/docs/Relude-Extra-Tuple.html

toFst :: (a -> b) -> a -> Record (s :-> b : s' :-> a : '[])
toFst f x = f x :*: x :*: RNil

toSnd :: (a -> b) -> a -> Record (s :-> a : s' :-> b : '[])
toSnd f x = x :*: f x :*: RNil

fmapToFst :: Functor f => (a -> b) -> f a -> f (Record (s :-> b : s' :-> a : '[]))
fmapToFst = fmap . toFst

fmapToSnd :: Functor f => (a -> b) -> f a -> f (Record (s :-> a : s' :-> b : '[]))
fmapToSnd = fmap . toSnd

traverseToFst :: Applicative m => (a -> m b) -> a -> m (Record (s :-> b : s' :-> a : '[]))
traverseToFst f x =  (:*: x :*: RNil) <$> f x

traverseToSnd :: Applicative m => (a -> m b) -> a -> m (Record (s :-> a : s' :-> b : '[]))
traverseToSnd f x =  (\y -> x :*: y :*: RNil) <$> f x

fanout :: (x -> a) -> (x -> b) -> x -> Record (s :-> a : s' :-> b : '[])
fanout f g x = f x :*: g x :*: RNil

fanoutM :: Applicative m => (x -> m a) -> (x -> m b) -> x -> m (Record (s :-> a : s' :-> b : '[]))
fanoutM f g x = (\y z -> y :*: z :*: RNil) <$> f x <*> g x

Given the names it would be expected that these are imported qualified. Do you think there could be a home for these?

template-haskell 2.17

The new template haskell in ghc 9 offered these migration instructions for TyVarBndr

https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.0#template-haskell-217

I've naively attempted to resolve this by setting TyVarBndrSpec here

locallycompact@73cbba0

But I get one type error.

composite-base                > /home/lc/Source/github.com/composite/composite-base/src/Composite/TH.hs:163:59: error:
composite-base                >     • Couldn't match type ‘()’ with ‘Specificity’
composite-base                >       Expected: Control.Lens.Getter.Getting
composite-base                >                   (base-4.15.0.0:Data.Semigroup.Internal.Endo
composite-base                >                      [(Name, [TyVarBndrSpec], Type)])
composite-base                >                   [Dec]
composite-base                >                   (Name, [TyVarBndrSpec], Type)
composite-base                >         Actual: ((Name, [Language.Haskell.TH.Lib.Internal.TyVarBndrUnit],
composite-base                >                   Type)
composite-base                >                  -> Data.Functor.Const.Const
composite-base                >                       (base-4.15.0.0:Data.Semigroup.Internal.Endo
composite-base                >                          [(Name, [TyVarBndrSpec], Type)])
composite-base                >                       (Name, [Language.Haskell.TH.Lib.Internal.TyVarBndrUnit], Type))
composite-base                >                 -> [Dec]
composite-base                >                 -> Data.Functor.Const.Const
composite-base                >                      (base-4.15.0.0:Data.Semigroup.Internal.Endo
composite-base                >                         [(Name, [TyVarBndrSpec], Type)])
composite-base                >                      [Dec]
composite-base                >     • In the first argument of ‘toListOf’, namely ‘(each . _TySynD)’
composite-base                >       In the second argument of ‘(.)’, namely ‘toListOf (each . _TySynD)’
composite-base                >       In the second argument of ‘(.)’, namely
composite-base                >         ‘map fieldDecMay . toListOf (each . _TySynD)’
composite-base                >     |
composite-base                > 163 |   let fieldDecs = catMaybes . map fieldDecMay . toListOf (each . _TySynD) $ decs

I can't really see what's going on here, but _TySynD doesn't look like something I want to change, but if I change these all to TyVarBndrUnit, then I get an error trying to use ForallT, which also doesn't look like like something I want to change.

composite-base                > /home/lc/Source/github.com/composite/composite-base/src/Composite/TH.hs:220:30: error:
composite-base                >     • Couldn't match type ‘()’ with ‘Specificity’
composite-base                >       Expected: [TyVarBndr Specificity]
composite-base                >         Actual: [TyVarBndr ()]
composite-base                >     • In the first argument of ‘ForallT’, namely ‘lensBinders’
composite-base                >       In the second argument of ‘SigD’, namely
composite-base                >         ‘(ForallT lensBinders lensContext lensType)’
composite-base                >       In the expression:
composite-base                >         SigD lensName (ForallT lensBinders lensContext lensType)
composite-base                >     |
composite-base                > 220 |     , SigD lensName (ForallT lensBinders lensContext lensType)
composite-base                >     |                              ^^^^^^^^^^^
composite-base                >
composite-base                > /home/lc/Source/github.com/composite/composite-base/src/Composite/TH.hs:240:31: error:
composite-base                >     • Couldn't match type ‘()’ with ‘Specificity’
composite-base                >       Expected: [TyVarBndr Specificity]
composite-base                >         Actual: [TyVarBndr ()]
composite-base                >     • In the first argument of ‘ForallT’, namely ‘prismBinders’
composite-base                >       In the second argument of ‘SigD’, namely
composite-base                >         ‘(ForallT prismBinders prismContext prismType)’
composite-base                >       In the expression:
composite-base                >         SigD prismName (ForallT prismBinders prismContext prismType)
composite-base                >     |
composite-base                > 240 |     , SigD prismName (ForallT prismBinders prismContext prismType)

Aeson boilerplate

Hi, returning to the aeson boilerplate problem.

I've been experimenting using typemap-rep https://hackage.haskell.org/package/typerep-map to store a bunch of essentially first class defaults. If I do something like

fModifiedField :: JsonField e FModified               
fModifiedField = field iso8601DateTimeJsonFormat                

fPrettyDateField :: JsonField e FPrettyDate
fPrettyDateField = field (dateTimeJsonFormat defaultTimeLocale (regularDateTimeFormat "%A, %B %d, %Y" "yyyy-mm-dd" :| []))

fIdField :: JsonField e FId
fIdField = field textJsonFormat

fUrlField :: JsonField e FUrl
fUrlField = field textJsonFormat

defaultFields :: TypeRepMap (JsonField e)
defaultFields = GHC.Exts.fromList [ WrapTypeable fModifiedField
                                  , WrapTypeable fPrettyDateField  
                                  , WrapTypeable fIdField
                                  , WrapTypeable fUrlField]
                                                       
a :: (Typeable x, Show x, MonadThrow m) => TypeRepMap (JsonField e) -> Identity x -> m ((JsonField e) x)
a fs (Identity x) = case Data.TypeRepMap.lookup fs of                                                 
                      Just x -> return x
                      Nothing -> throwM $ F $ "Could not find " <> show x
 
rtraverse' 
  :: (AllHave '[Typeable, Show] rs, Applicative h)
  => (forall x. (Typeable x, Show x) => f x -> h (g x))    
  -> Rec f rs
  -> h (Rec g rs)
rtraverse' _ RNil      = pure RNil 
rtraverse' f (x :& xs) = (:&) <$> f x <*> rtraverse' f xs
  
b :: (AllHave '[Typeable, Show] x, MonadThrow m) => Rec Identity x -> m (Rec (JsonField e) x)        
b = rtraverse' (a defaultFields)

Then this allows me to basically just have a bag of formatting data for each field by symbol and pass that around, but is there a way to do rtraverse' without reimplementing it?

Combining formatters (UTCTime)

Hi, I'm struggling to figure out from the examples how to format a UTCTime field. So far I have this.

type FId   = "id"   :-> Int
type FName = "name" :-> Text
type FMod  = "mod" :-> UTCTime
type User = '[FId, FName, FMod]

userFormat :: JsonFormat e (Record User)
userFormat = recordJsonFormat $ set (rlens' (Proxy :: Proxy FMod)) (field' iso8601DateTimeJsonFormat) defaultJsonFormatRecord

alice :: Record User
alice = 1 :*: "Alice" :*: (UTCTime (ModifiedJulianDay 58025) (fromRational 72151.986)) :*: RNil

aliceJson :: Aeson.Value
aliceJson = toJsonWithFormat userFormat alice

which results in

/home/lc/foo/src/Lib.hs:24:38: error:
    • No instance for (Functor (Composite.Aeson.Record.JsonField e))
        arising from a use of ‘rlens'’
    • In the first argument of ‘set’, namely
        ‘(rlens' (Proxy :: Proxy FMod))’
      In the second argument of ‘($)’, namely
        ‘set
           (rlens' (Proxy :: Proxy FMod))
           (field' iso8601DateTimeJsonFormat)
           defaultJsonFormatRecord’
      In the expression:
        recordJsonFormat
          $ set
              (rlens' (Proxy :: Proxy FMod))
              (field' iso8601DateTimeJsonFormat)
              defaultJsonFormatRecord
   |
24 | userFormat = recordJsonFormat $ set (rlens' (Proxy :: Proxy FMod)) (field' iso8601DateTimeJsonFormat) defaultJsonFormatRecord
   |                                      ^^^^^^^^^^^^^^^^^^^^^^^^^^^^

/home/lc/foo/src/Lib.hs:24:103: error:
    • No instance for (Composite.Aeson.Formats.Default.DefaultJsonFormat
                         UTCTime)
        arising from a use of ‘defaultJsonFormatRecord’
    • In the third argument of ‘set’, namely ‘defaultJsonFormatRecord’
      In the second argument of ‘($)’, namely
        ‘set
           (rlens' (Proxy :: Proxy FMod))
           (field' iso8601DateTimeJsonFormat)
           defaultJsonFormatRecord’
      In the expression:
        recordJsonFormat
          $ set
              (rlens' (Proxy :: Proxy FMod))
              (field' iso8601DateTimeJsonFormat)
              defaultJsonFormatRecord
   |
24 | userFormat = recordJsonFormat $ set (rlens' (Proxy :: Proxy FMod)) (field' iso8601DateTimeJsonFormat) defaultJsonFormatRecord

currying/uncurry against underlying values

Working on adding more information to this. I'm trying to get the curry/uncurry functions working in Data.Vinyl.Curry to use against normal functions.

http://hackage.haskell.org/package/vinyl-0.13.0/docs/Data-Vinyl-Curry.html

They don't work out of the box for two reasons. One is that the Identity types are different in Vinyl, so we need a new function and type family, but that still doesn't work because

type family CurriedC ts a where        
  CurriedC '[] a = a
  CurriedC ((s :-> t) ': ts) a = t -> CurriedC ts a    
  
runcurry'' :: CurriedC ts a -> Rec Identity ts -> a                       
runcurry'' x RNil               = x
runcurry'' f (Identity x :& xs) = runcurry'' (f $ (getVal x)) xs         
    • Could not deduce: r ~ (s0 :-> t0)
      from the context: ts ~ (r : rs)
        bound by a pattern with constructor:
                   :& :: forall u (a :: u -> *) (r :: u) (rs :: [u]).
                         a r -> Rec a rs -> Rec a (r : rs),
                 in an equation for ‘runcurry''’
        at src/Shakebook/Conventions.hs:248:15-30
      ‘r’ is a rigid type variable bound by
        a pattern with constructor:
          :& :: forall u (a :: u -> *) (r :: u) (rs :: [u]).
                a r -> Rec a rs -> Rec a (r : rs),
        in an equation for ‘runcurry''’
        at src/Shakebook/Conventions.hs:248:15-30
    • In the first argument of ‘getVal’, namely ‘x’
      In the second argument of ‘($)’, namely ‘getVal x’
      In the first argument of ‘runcurry''’, namely ‘(f $ getVal x)’
    • Relevant bindings include
        x :: r (bound at src/Shakebook/Conventions.hs:248:24)
    |       
248 | runcurry'' f (Identity x :& xs) = runcurry'' (f $ getVal x) xs

Edit: I was able to make some progress using the HKD interface.

instance KnownSymbol s => IsoHKD Identity (s :-> a) where
  type HKD Identity (s :-> a) = a
  unHKD = Identity . Val
  toHKD (Identity (Val x)) = x

Now I can do

let p = 1 :*: 2 :*: RNil :: Record ("a" :-> Int : "b" :-> Int : '[])
runcurryX (+) p

I'm not sure if I can tease the Identity part out of the instance, but it's a start.

Can we release composite independently of the other projects?

Hi. I don't use any of the other projects in this repository and it's annoying to have to upgrade things like ekg-json for a hackage release of the core library. It's blocking adoption of composite in other areas with there not being a ghc 9.2 release available. Can composite have its own repository for the core functionality?

NFData, Hashable, Binary Instances

Hi, these aren't dependencies of composite so I was planning on making orphan packages for all of these three (since they're need for Shake), unless you'd consider any of these potentially in-scope of composite-base and wanted to include a dependency -
They look like this.

instance Hashable a => Hashable (s :-> a) where
  hashWithSalt n x = hashWithSalt n $ getVal x

instance Binary a => Binary (s :-> a) where
  put = put . getVal
  get = fmap (runIdentity . val) get

instance NFData (s :-> a) where
  rnf x = seq x ()
  
instance Binary (Record '[])
 
instance (Binary a, Binary (Record xs), x ~ (s :-> a)) => Binary (Record (x : xs)) where
  put (x :*: xs) = put x >> put xs
  get = liftA2 (:*:) get get

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

instance (NFData a, NFData (Record xs), x ~ (s :-> a)) => NFData (Record (x : xs)) where                 
  rnf (x :*: xs) = rnf x `seq` rnf xs

instance Hashable (Record '[]) where
  hashWithSalt n RNil = n `hashWithSalt` ()

instance (Hashable a, Hashable (Record xs), x ~ (s :-> a)) => Hashable (Record (x : xs)) where
  hashWithSalt n (x :*: xs) = n `hashWithSalt` x `hashWithSalt` xs

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.