[Haskell-cafe] Functor instance for GADT (was: 123)

Dmitriy Matrosov sgf.dma at gmail.com
Wed Aug 23 19:14:19 UTC 2017


  On 08/23/2017 12:50 AM, Mario Blažević wrote:
  > On 2017-08-16 04:54 PM, Dmitriy Matrosov wrote:
  >> And even sent the answer not to the list.. Huh.
  >
  > I'm not sure I fully undestand your use case, but your examples can be
  > handled by the rank2classes package
  > (http://hackage.haskell.org/package/rank2classes).
  >
  >
  >> I want to have a type with many records:
  >>
  >>> data Volume t     = Volume
  >>>                       { _volName  :: t String
  >>>                       , _volSize  :: t Int
  >>>                       }
  >>>
  >>> showVolume :: (Show (t String), Show (t Int)) => Volume t -> String
  >>> showVolume x      = "Volume " ++ show (_volName x) ++ ", " ++ show
  >> (_volSize x)
  >>
  >> with instances parametrized by some other type. E.g. i want to define a
  >> `Monoid` based on that other type properties:
  >>
  >>> instance Alternative t => Monoid (Volume t) where
  >>>   mempty          = Volume {_volName = empty, _volSize = empty}
  >>>   x `mappend` y   = Volume
  >>>                       { _volName = _volName x <|> _volName y
  >>>                       , _volSize = _volSize x <|> _volSize y
  >>>                       }
  >
  >
  > instance Rank2.Apply Volume where
  >     x <*> y   = Volume
  >                     { _volName = _volName x `Rank2.apply` _volName y
  >                     , _volSize = _volSize x `Rank2.apply` _volSize y
  >                     }
  >
  > instance Rank2.Applicative Volume where
  >     pure x = Volume {_volName = x, _volSize = x}
  >
  > instance Alternative t => Monoid (Volume t) where
  >    mempty          = Rank2.pure empty
  >    x `mappend` y   = Rank2.liftA2 (<|>) x y
  >

Yes, that's almost exactly what i want! I said "almost", because i want 
to use
it with GADT, which `mappend`-s different types differently. So, when i
`mappend` `Volume`-s, different fields are summed differently.

Here is the code i have so far:

 > {-# LANGUAGE GADTs            #-}
 > {-# LANGUAGE StandaloneDeriving #-}
 > {-# LANGUAGE RecordWildCards  #-}
 > {-# LANGUAGE ScopedTypeVariables  #-}
 >
 > import Control.Applicative
 > import Data.Monoid
 > import Data.Functor.Classes
 >
 > data Volume t     = Volume
 >                       { _volName  :: t String
 >                       , _volSize  :: t Int
 >                       }
 >
 >
 > instance Alternative t => Monoid (Volume t) where
 >   mempty          = Volume {_volName = empty, _volSize = empty}
 >   x `mappend` y   = Volume
 >                       { _volName = _volName x <|> _volName y
 >                       , _volSize = _volSize x <|> _volSize y
 >                       }

Then 'Show' defined with the help of 'Show1' as suggested by Isaac Elliott:

 > instance Show1 t => Show (Volume t) where
 >   showsPrec n Volume {..} = showString "Volume "
 >                               . showsPrec1 n _volName
 >                               . showsPrec1 n _volSize

or alternative approach suggested by Dmitry Olshansky:

 > --instance forall t. (Functor t, Foldable t) => Show (Volume t) where
 > --  showsPrec n Volume {..} = showString "Volume "
 > --                              . showsPrec1' n _volName
 > --                              . showsPrec1' n _volSize
 > --    where
 > --      liftShowsPrec' :: (Int -> a -> ShowS) -> Int -> t a -> ShowS
 > --      liftShowsPrec' sp m = appEndo . foldMap id . fmap (Endo . sp m)
 > --      showsPrec1' :: Show a => Int -> t a -> ShowS
 > --      showsPrec1' m       = liftShowsPrec' showsPrec m

That's the part, which was in the original question, and it works fine now.
Thanks to all! But there is also the other part, which i was unaware of.

 > data Config a where
 >   Empty :: Config a
 >   Name :: Last String -> Config String
 >   Size :: Num a => Sum a  -> Config a
 > deriving instance Show a => Show (Config a)

First, i need some convenient way (don't think about it yet) to construct a
values like:

 > vconf1 :: Volume Config
 > vconf1        = Volume
 >                   { _volName = Name (Last (Just "abc"))
 >                   , _volSize = Size (Sum 12)
 >                   }
 > vconf2 :: Volume Config
 > vconf2        = Volume
 >                   { _volName = Name (Last (Just "def"))
 >                   , _volSize = Size (Sum 100)
 >                   }

Second, probably more importantly, i need to `mappend` them.  Essentially, i
want `Config` to behave like

 > instance Monoid (Config a) where
 >   mempty  = Empty
 >   (Name x) `mappend` (Name y)     = Name (x `mappend` y)
 >   (Size x) `mappend` (Size y)     = Size (x `mappend` y)
 >   x        `mappend` Empty        = x
 >   Empty    `mappend` y            = y

but i need it to be an `Alternative`. And i can't define a `Functor` 
instance
for it.




More information about the Haskell-Cafe mailing list