module ProjectM36.Tupleable where
import ProjectM36.Base
import ProjectM36.Error
import ProjectM36.TupleSet
import ProjectM36.Tuple
import ProjectM36.Atomable
import ProjectM36.DataTypes.Primitive
import ProjectM36.Attribute hiding (null)
import GHC.Generics
import qualified Data.Vector as V
import qualified Data.Text as T
import Data.Monoid
import Data.Proxy
import Data.Foldable
toInsertExpr :: forall a t. (Tupleable a, Traversable t) => t a -> RelVarName -> Either RelationalError DatabaseContextExpr
toInsertExpr vals rvName = do
let attrs = toAttributes (Proxy :: Proxy a)
tuples <- mkTupleSet attrs $ toList (fmap toTuple vals)
let rel = MakeStaticRelation attrs tuples
pure (Insert rvName rel)
toDefineExpr :: forall a proxy. Tupleable a => proxy a -> RelVarName -> DatabaseContextExpr
toDefineExpr _ rvName = Define rvName (map NakedAttributeExpr (V.toList attrs))
where
attrs = toAttributes (Proxy :: Proxy a)
class Tupleable a where
toTuple :: a -> RelationTuple
fromTuple :: RelationTuple -> Either RelationalError a
toAttributes :: proxy a -> Attributes
default toTuple :: (Generic a, TupleableG (Rep a)) => a -> RelationTuple
toTuple v = toTupleG (from v)
default fromTuple :: (Generic a, TupleableG (Rep a)) => RelationTuple -> Either RelationalError a
fromTuple tup = to <$> fromTupleG tup
default toAttributes :: (Generic a, TupleableG (Rep a)) => proxy a -> Attributes
toAttributes _ = toAttributesG (from (undefined :: a))
class TupleableG g where
toTupleG :: g a -> RelationTuple
toAttributesG :: g a -> Attributes
fromTupleG :: RelationTuple -> Either RelationalError (g a)
instance (Datatype c, TupleableG a) => TupleableG (M1 D c a) where
toTupleG (M1 v) = toTupleG v
toAttributesG (M1 v) = toAttributesG v
fromTupleG v = M1 <$> fromTupleG v
instance (Constructor c, TupleableG a, AtomableG a) => TupleableG (M1 C c a) where
toTupleG (M1 v) = RelationTuple attrs atoms
where
attrsToCheck = toAttributesG v
counter = V.generate (V.length attrsToCheck) id
attrs = V.zipWith (\num attr@(Attribute name typ) -> if T.null name then
Attribute ("attr" <> T.pack (show (num + 1))) typ
else
attr) counter attrsToCheck
atoms = V.fromList (toAtomsG v)
toAttributesG (M1 v) = toAttributesG v
fromTupleG tup = M1 <$> fromTupleG tup
instance (TupleableG a, TupleableG b) => TupleableG (a :*: b) where
toTupleG = error "toTupleG"
toAttributesG ~(x :*: y) = toAttributesG x V.++ toAttributesG y
fromTupleG tup = (:*:) <$> fromTupleG tup <*> fromTupleG (trimTuple 1 tup)
--selector/record
instance (Selector c, AtomableG a) => TupleableG (M1 S c a) where
toTupleG = error "toTupleG"
toAttributesG m@(M1 v) = V.singleton (Attribute name aType)
where
name = T.pack (selName m)
aType = toAtomTypeG v
fromTupleG tup = if null name then
M1 <$> atomv (V.head (tupleAtoms tup))
else do
atom <- atomForAttributeName (T.pack name) tup
val <- atomv atom
pure (M1 val)
where
expectedAtomType = atomType (V.head (toAttributesG (undefined :: M1 S c a x)))
atomv atom = maybe (Left (AtomTypeMismatchError
expectedAtomType
(atomTypeForAtom atom)
)) Right (fromAtomG atom [atom])
name = selName (undefined :: M1 S c a x)
instance TupleableG U1 where
toTupleG _= emptyTuple
toAttributesG _ = emptyAttributes
fromTupleG _ = pure U1