[Haskell-cafe] Layer on a layer of record syntax in the type synonym?

Nicolas Trangez nicolas at incubaid.com
Fri Dec 21 15:01:51 CET 2012


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




More information about the Haskell-Cafe mailing list