Layer on a layer of record syntax in the type synonym?

Using a simple type I gave earlier from my monadic type question... code: -------- data Socket3 a b c = Socket3 a b c deriving (Show) -------- Is it possible somehow to layer on record syntax onto a synonym of the type? The idea would be something like this... code: -------- type SpaceShip = Socket3 { engine :: Last Engine , hull :: Last Hull , guns :: [Guns] } -------- ...purely for the convenience. But this doesn't seem to work with "type" as it assumes you are referring to already made constructors, and evidently "newtype" only allows use of a single record. I could wrap it in a normal "data" declaration but that would add an extra layer of complexity I think. -- frigidcode.com

On 22 December 2012 00:36, Christopher Howard
Using a simple type I gave earlier from my monadic type question...
code: -------- data Socket3 a b c = Socket3 a b c deriving (Show) --------
Is it possible somehow to layer on record syntax onto a synonym of the type?
The idea would be something like this...
code: -------- type SpaceShip = Socket3 { engine :: Last Engine , hull :: Last Hull , guns :: [Guns] } --------
...purely for the convenience. But this doesn't seem to work with "type" as it assumes you are referring to already made constructors, and evidently "newtype" only allows use of a single record. I could wrap it in a normal "data" declaration but that would add an extra layer of complexity I think.
No, you can't suddenly add records in just for a type alias. You might be able to create lenses though for setters/getters, though if you just want getters you can just write them yourself.
-- frigidcode.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

Hi Christopher, On Fri, Dec 21, 2012 at 04:36:04AM -0900, Christopher Howard wrote:
Using a simple type I gave earlier from my monadic type question...
code: -------- data Socket3 a b c = Socket3 a b c deriving (Show) --------
Is it possible somehow to layer on record syntax onto a synonym of the type?
The idea would be something like this...
code: -------- type SpaceShip = Socket3 { engine :: Last Engine , hull :: Last Hull , guns :: [Guns] } --------
...purely for the convenience. But this doesn't seem to work with "type" as it assumes you are referring to already made constructors, and evidently "newtype" only allows use of a single record. I could wrap it in a normal "data" declaration but that would add an extra layer of complexity I think.
I don't know in which context you would like to use the SpaceShip type, but the solution using the very generic Socket3 might bite you later, because you don't have a concrete type for your SpaceShip and can't identify it. Why having a Socket3 in the first place, what's the point of it?
-- frigidcode.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 12/21/2012 04:52 AM, Daniel Trstenjak wrote:
Why having a Socket3 in the first place, what's the point of it?
The idea was to have some generic structures (Sockets) which were already instanced into the Monoids-within-Monoids abstraction, yet could still be made concrete into anything more specific. So, I have... code: -------- data Socket3 a b c = Socket3 a b c deriving (Show) instance (Monoid a, Monoid b, Monoid c) => Monoid (Socket3 a b c) where mempty = Socket3 mempty mempty mempty Socket3 a b c `mappend` Socket3 w x y = Socket3 (a <> w) (b <> x) (c <> y) nullSocket3 :: (Monoid a, Monoid b, Monoid c) => Socket3 a b c nullSocket3 = Socket3 mempty mempty mempty -------- ...which allows me to have... code: -------- type ShipSys = Socket3 (Last Engine) (Last RotThruster) [LinThruster] nullShipSys :: ShipSys nullShipSys = nullSocket3 setEngineSocket (Socket3 a b c) x = Socket3 x b c engineSys :: Engine -> ShipSys engineSys a = setEngineSocket nullShipSys (Last (Just a)) mk1Engine = engineSys (Engine 100 1 "Mark I") -- etc. -------- And so, with each individual component being wrapped as a generic ShipSys (ship system), I can make a complete system simply by composition: code: -------- h> :t mk1Engine mk1Engine :: ShipSys h> :t stdRearThruster stdRearThruster :: ShipSys h> :t stdFrontThruster stdFrontThruster :: ShipSys h> :t stdRotThruster stdRotThruster :: Power -> ShipSys h> mk1Engine <> stdRearThruster <> stdFrontThruster <> stdRotThruster 10 Socket3 (Last {getLast = Just (Engine 100.0 1.0 "Mark I")}) (Last {getLast = Just (RotThruster 10.0)}) [LinThruster 3.1415927 1.0,LinThruster 0.0 0.5] -------- This seems to work well enough so far. But the issue I was concerned about is: if I can't layer record syntax onto the type synonym, then I have to rewrite a whole bunch of getters / setters each time I want to add an attribute (e.g., requiring a switch from a Socket3 to a Socket4.) If this is the case, then perhaps it would be better just to define the ShipSys type directly, and directly instance it into the monoid abstraction. -- frigidcode.com

You could look into the "Generic Monoid" solution proposed in your
other thread, then you wouldn't need your "Socket" types - you would
use the "Generic Monoid" machinery to make a Monoid instance for
whatever type needed it.
This approach loses some type-safety, as you might pass on version of
a Scoket3 to a function that was meant to take a different type of
Socket3.
On Fri, Dec 21, 2012 at 4:50 PM, Christopher Howard
On 12/21/2012 04:52 AM, Daniel Trstenjak wrote:
Why having a Socket3 in the first place, what's the point of it?
The idea was to have some generic structures (Sockets) which were already instanced into the Monoids-within-Monoids abstraction, yet could still be made concrete into anything more specific.
So, I have...
code: -------- data Socket3 a b c = Socket3 a b c deriving (Show)
instance (Monoid a, Monoid b, Monoid c) => Monoid (Socket3 a b c) where mempty = Socket3 mempty mempty mempty Socket3 a b c `mappend` Socket3 w x y = Socket3 (a <> w) (b <> x) (c <> y)
nullSocket3 :: (Monoid a, Monoid b, Monoid c) => Socket3 a b c nullSocket3 = Socket3 mempty mempty mempty --------
...which allows me to have...
code: -------- type ShipSys = Socket3 (Last Engine) (Last RotThruster) [LinThruster]
nullShipSys :: ShipSys nullShipSys = nullSocket3
setEngineSocket (Socket3 a b c) x = Socket3 x b c
engineSys :: Engine -> ShipSys engineSys a = setEngineSocket nullShipSys (Last (Just a))
mk1Engine = engineSys (Engine 100 1 "Mark I")
-- etc. --------
And so, with each individual component being wrapped as a generic ShipSys (ship system), I can make a complete system simply by composition:
code: -------- h> :t mk1Engine mk1Engine :: ShipSys h> :t stdRearThruster stdRearThruster :: ShipSys h> :t stdFrontThruster stdFrontThruster :: ShipSys h> :t stdRotThruster stdRotThruster :: Power -> ShipSys h> mk1Engine <> stdRearThruster <> stdFrontThruster <> stdRotThruster 10 Socket3 (Last {getLast = Just (Engine 100.0 1.0 "Mark I")}) (Last {getLast = Just (RotThruster 10.0)}) [LinThruster 3.1415927 1.0,LinThruster 0.0 0.5] --------
This seems to work well enough so far. But the issue I was concerned about is: if I can't layer record syntax onto the type synonym, then I have to rewrite a whole bunch of getters / setters each time I want to add an attribute (e.g., requiring a switch from a Socket3 to a Socket4.) If this is the case, then perhaps it would be better just to define the ShipSys type directly, and directly instance it into the monoid abstraction.
-- frigidcode.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, 2012-12-21 at 04:36 -0900, Christopher Howard wrote:
Using a simple type I gave earlier from my monadic type question...
code: -------- data Socket3 a b c = Socket3 a b c deriving (Show) --------
Is it possible somehow to layer on record syntax onto a synonym of the type?
The idea would be something like this...
code: -------- type SpaceShip = Socket3 { engine :: Last Engine , hull :: Last Hull , guns :: [Guns] } --------
...purely for the convenience. But this doesn't seem to work with "type" as it assumes you are referring to already made constructors, and evidently "newtype" only allows use of a single record. I could wrap it in a normal "data" declaration but that would add an extra layer of complexity I think.
Although this 'Socket3' data type which all of a sudden should be aliased as 'SpaceShip' feels/looks really strange (are you sure that's the right way to reach whatever the goal is?), you could use lenses: import Control.Lens data Socket3 a b c = Socket3 a b c deriving (Show) data Last a = Last a deriving Show data Engine = Engine deriving Show data Hull = Hull deriving Show data Gun = Gun deriving Show type SpaceShip = Socket3 (Last Engine) (Last Hull) [Gun] engine :: Simple Lens SpaceShip (Last Engine) engine = lens get lset where get (Socket3 a _ _) = a lset (Socket3 _ b c) a' = Socket3 a' b c hull :: Simple Lens SpaceShip (Last Hull) hull = lens get lset where get (Socket3 _ b _ ) = b lset (Socket3 a _ c) b' = Socket3 a b' c guns :: Simple Lens SpaceShip [Gun] guns = lens get lset where get (Socket3 _ _ c) = c lset (Socket3 a b _) = Socket3 a b main :: IO () main = do print $ s0 ^. engine print $ s0 ^. guns let s1 = guns .~ [Gun, Gun] $ s0 print s1 print $ s1 ^. guns where s0 :: SpaceShip s0 = Socket3 (Last Engine) (Last Hull) [] (I'm no Lens expert so maybe there are better ways than manually creating these Lens instances, or make them shorter/abstract something out) Nicolas
participants (5)
-
Antoine Latter
-
Christopher Howard
-
Daniel Trstenjak
-
Ivan Lazar Miljenovic
-
Nicolas Trangez