Search code examples
haskellfunctorhigher-kinded-types

Working with data types parameterized by a functor


I recently defined a type whose fields I might fail to compute:

data Foo = Foo {x, y :: Int, others :: NonEmpty Int}

data Input

computeX, computeY :: Input -> Maybe Int
computeOthers :: Input -> Maybe (NonEmpty Int)

Now, one obvious thing I might do would be to just use liftA3:

foo :: Input -> Maybe Foo
foo i = liftA3 Foo (computeX i) (computeY i) (computeOthers i)

That works fine, but I thought it might be interesting to generalize Foo to hold Maybes as well, and then transform one type of Foo to another. In some similar cases, I could give the Foo type a type parameter and derive Traversable. Then after creating a Foo (Maybe Int), I could invert the whole thing at once with sequenceA :: Foo (Maybe Int) -> Maybe (Foo Int). But this doesn't work here, because my function doesn't give me a NonEmpty (Maybe Int), it gives me a Maybe (NonEmpty Int).

So I thought I'd try parameterizing by a functor instead:

data Foo f = Foo {x, y :: f Int, others :: f (NonEmpty Int)}

But then the question is, how do I turn a Foo Maybe into a Maybe (Foo Identity)? Obviously I can write that function by hand: it's isomorphic to the liftA3 stuff above. But is there some parallel of Traversable for this higher-order type, so that I can apply a more general function to this problem rather than re-doing it with a bespoke function?


Solution

  • Such data types are called "Higher-Kinded Data" (HKD). Manipulating them is often done with Generics or Template Haskell.

    There are libraries like higgledy which provide built-in functionality for HKD. I believe construct is the function you are looking for:

    {-# LANGUAGE DeriveGeneric #-}
    
    import Data.Generic.HKD
    import GHC.Generics
    import Data.Monoid
    
    data Foo = Foo { x, y :: Int, z :: [Int] }
      deriving (Generic, Show)
    
    emptyFoo :: HKD Foo Last
    emptyFoo = mempty
    
    sampleFoo :: HKD Foo Last
    sampleFoo = deconstruct (Foo 1 2 [3])
    
    emptyFoo' :: Last Foo
    emptyFoo' = construct emptyFoo
    
    sampleFoo' :: Last Foo
    sampleFoo' = construct sampleFoo
    
    main = do
      print emptyFoo'
      print sampleFoo'
    

    This will print:

    Last {getLast = Nothing}
    Last {getLast = Just (Foo {x = 1, y = 2, z = [3])}
    

    Edit: I just found out that a much more popular library is barbies (higgledy also depends on barbies). The function that you are looking for is also present in that library as an application of btraverse:

    {-# LANGUAGE DeriveGeneric #-}
    {-# LANGUAGE DeriveAnyClass #-}
    {-# LANGUAGE StandaloneDeriving #-}
    {-# LANGUAGE UndecidableInstances #-}
    
    import Data.List.NonEmpty
    import Barbies
    import GHC.Generics
    import Data.Functor.Identity
    
    data Foo f = Foo {x, y :: f Int, others :: f (NonEmpty Int)}
      deriving (Generic, FunctorB, TraversableB, ConstraintsB)
    
    deriving instance AllBF Show f Foo => Show (Foo f)
    
    f :: Applicative f => Foo f -> f (Foo Identity)
    f = btraverse (fmap Identity)
    
    main :: IO ()
    main = do
      print (f (Foo (Just 1) (Just 2) (Just (3 :| []))))
    

    This prints:

    Just (Foo {x = Identity 1, y = Identity 2, others = Identity (3 :| [])})