project-m36 icon indicating copy to clipboard operation
project-m36 copied to clipboard

Define a Tupleable instance with a subrelation

Open Valdsonjr opened this issue 3 years ago • 7 comments

Right now, haskell datatypes with list attributes are derived as t :: List (a :: SomeTypeT) is there a way of forcing the deriving mechanism to use t :: relation {a::SomeTypeT} instead?

Valdsonjr avatar Sep 17 '22 15:09 Valdsonjr

I couldn't find the code but I once wrote something like an instance Atomable a => Atomable Set a where toAtom = -- relation{element a}) And the Tupleable deriving mechanism works pretty well.

For what its worth, relation{element a} is a set and cannot keep duplicated elements while relation{index Integer, element a} can.

YuMingLiao avatar Sep 18 '22 14:09 YuMingLiao

Thanks, I will try that!

Do you guys think it's something useful to have? Should I make a pull request?

Valdsonjr avatar Sep 19 '22 02:09 Valdsonjr

A shortcut here could be to wrap the specific list item with newtype and add an Atomable instance for it that does what you want. In general, Tupleable and Atomable don't support subrelations by default because doing so would make the type variables more annoying.

Certainly, if you make some progress on this front, a PR would be much appreciated.

agentm avatar Sep 23 '22 00:09 agentm

@Valdsonjr , were you able to resolve this issue?

agentm avatar Sep 28 '22 17:09 agentm

@agentm I made it work with this ugly thing:

{-# LANGUAGE ScopedTypeVariables #-}

-- 'throws' something that is not a member of the Exception type class
throwIfLeft :: (Show a) => Either a b -> b
throwIfLeft = either (error . show) id

instance (Tupleable a, NFData a, Ord a, Serialise a, Show a) => Atomable (Set a) where
    toAtom :: Set a -> Atom
    toAtom set = RelationAtom (Relation attrs tuples)
        where
        tuples = RelationTupleSet $ map toTuple $ toList set
        attrs = toAttributes (Proxy :: Proxy a)

    fromAtom :: Atom -> Set a
    fromAtom (RelationAtom (Relation _ (RelationTupleSet tuples))) =
        fromList $ map (throwIfLeft . fromTuple) tuples
    fromAtom _ = error "wrong Atom constructor for (Set a)"

    toAtomType :: proxy (Set a) -> AtomType
    toAtomType _ = RelationAtomType (toAttributes (Proxy :: Proxy a))

I really wish I could remove some of those constraints, but at least it works for my toy programs

Valdsonjr avatar Sep 28 '22 23:09 Valdsonjr

That code is pretty straightforward- I'll wrap it into Project:M36, if you don't mind.

What bothers you about the constraints?

agentm avatar Sep 29 '22 01:09 agentm

@agentm Sure! I can open the PR tomorrow night if you want. (and add the toAddTypeExpr)

What bothers you about the constraints?

I felt like there were too many constraints but on second thought I don't know of any other way

Valdsonjr avatar Sep 29 '22 13:09 Valdsonjr