{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE UndecidableInstances #-} module Composite.Sheet where import qualified Composite.Csv as Csv import Composite.Record import Control.Applicative import Data.Aeson as A import Data.ByteString.Base64 as B64 import Data.ByteString.Lazy (fromStrict, toStrict) import Data.Csv hiding (Record) import Data.Functor.Identity import Data.Proxy import Data.Text.Encoding import qualified Data.Vector as V import GHC.Generics -- | The SheetT type. This is a functor of hetrogenous records. -- A typical "SpreadSheet" might be something like `SheetT [] Identity` -- This provides a convenient newtype for deriving instances. newtype SheetT w f xs = SheetT { runSheetT :: w (Rec f xs) } type Sheet f xs = SheetT f Identity xs deriving stock instance Eq (w (Rec f xs)) => Eq (SheetT w f xs) deriving stock instance Show (w (Rec f xs)) => Show (SheetT w f xs) deriving stock instance Generic (SheetT w f xs) instance (ToNamedRecord (Record ixs), Csv.ToHeader (Record ixs)) => ToJSON (Sheet [] ixs) where toJSON (SheetT xs) = let z = encodeByName (Csv.extractRecHeader (Proxy @(Record ixs))) xs in A.String $ decodeUtf8 $ B64.encode $ toStrict $ z instance FromNamedRecord (Record ixs) => FromJSON (Sheet [] ixs) where parseJSON (String x) = do let k = case B64.decode $ encodeUtf8 x of Left e -> Left e Right a -> decodeByName . fromStrict $ a case k of Left e -> fail $ show e Right a -> pure $ SheetT $ V.toList $ snd a parseJSON _ = empty