7

Context

If we have

data Foo = Foo { x :: Maybe Int, y :: Maybe Text }

we can already build it up applicative-style in an Applicative context (here IO) as

myfoo :: IO Foo
myfoo = Foo <$> getEnvInt "someX" <*> getEnvText "someY"

Problem

What if one prefers to build with explicitly writing out the record field names? Such as:

myfoo = Foo { x = getEnvInt "someX", y = getEnvText "someY" }

This won't typecheck. One solution is

{-# LANGUAGE RecordWildCards #-}
myfoo = do
    x <- getEnvInt "someX"
    y <- getEnvText "someY"
    return $ Foo {..}

Which is not bad. But I wonder (at this point only for the sake of itself) if the following could work:

data FooC f = FooC { x :: f Int, y :: f Text }
type Foo = FooC Maybe

myfoo :: IO Foo
myfoo = genericsMagic $ FooC
    { x = someEnvInt "someX"
    , y = someEnvText "someY"
    }

I believe it can be done with bare GHC.Generics pattern matching, but that wouldn't have type safety, so I was looking for a stronger approach. I encountered generics-sop, which converts the record into a heterogeneous list, and comes with a seemingly handy hsequence operation.

Point where I'm stuck

generics-sop stores the Applicative's type in a separate type parameter of its heterogeneous list, and that is always I (Identity) when using the generated conversion. So I would need to map the hlist and remove the I from the elements which would effectively move the Applicative under I to the mentioned type parameter (it would be Comp IO Maybe), so I could use hsequence, and finally add back the Is so I can covert back to record.

But I don't know how to write a type signature for the I removal / addition function, which communicates that the types of the respective hlist elements change consistently by losing/gaining the outer type. Is this even possible?

ron
  • 9,262
  • 4
  • 40
  • 73
  • I'm not sure this will all work, or at least not as nicely as you imagine. Note that `FooC { x = someEnvInt "someX" , y = someEnvText "someY" }` won't compile by itself. If you change `someEnv___` to have signature `Data.Functor.Compose IO Maybe ___` you might have a chance then. But at that point, I'm not sure it would be worth it at all anymore... – Alec Oct 24 '16 at 10:57
  • @Alec: wrapping in Compose (or `generics-sop`'s equivalent) is acceptable. – ron Oct 24 '16 at 11:50
  • You don't need generics .. just write a function `(Applicative g, Applicative f) => FooC (Compose f g) -> f (FooC g)` (this function is essentially just `sequence`) - then change the type of `someEnvInt` to `Compose IO Maybe Int`. If you want you can do the 'uncomposition' using type families which would save you changing the type of `someEnvInt` but I personally don't think it's worth the effort. – user2407038 Oct 24 '16 at 14:09
  • @user2407038: I want to avoid hand-rolling the function, since 'Foo' can have a lot of fields, and then this is just boilerplate. That's why I wanted Generics. – ron Oct 29 '16 at 15:51

2 Answers2

0

But I don't know how to write a type signature for the I removal / addition function, which communicates that the types of the respective hlist elements change consistently by losing/gaining the outer type. Is this even possible?

I don't know how to do that either. A possible workaround (at the cost of some boilerplate) would be to use record pattern synonyms to construct the sum-of-products representation directly, while still being able to use named fields:

{-# language DeriveGeneric #-}
{-# language TypeFamilies #-}
{-# language TypeOperators #-}
{-# language PatternSynonyms #-}

import Data.Text
import qualified GHC.Generics as GHC
import Generics.SOP
import Text.Read

data Foo = Foo { x :: Int, y :: Text } deriving (Show, GHC.Generic)

instance Generic Foo

pattern Foo' :: t Int -> t Text -> SOP t (Code Foo)
pattern Foo' {x', y'} = SOP (Z (x' :* y' :* Nil))

readFooMaybe :: SOP (IO :.: Maybe) (Code Foo)
readFooMaybe = Foo'
             {
                x' = Comp (fmap readMaybe getLine)
             ,  y' = Comp (fmap readMaybe getLine)
             }

Testing it on ghci:

ghci> hsequence' readFooMaybe >>= print
12
"foo"
SOP (Z (Just 12 :* (Just "foo" :* Nil)))
danidiaz
  • 26,936
  • 4
  • 45
  • 95
0

The problem with Generics is that your FooC type has the kind (* -> *) -> * and, as far as I know, it's not possible to automatically derive a GHC.Generics instance for such a type. If you are open to a solution using Template Haskell it's relatively easy to write the TH code needed to automatically handle any record type.

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TemplateHaskell #-}

module AppCon where

import Control.Applicative
import Control.Compose ((:.), unO)
import Language.Haskell.TH

class AppCon t where
  appCon :: Applicative f => t (f :. g) -> f (t g)

deriveAppCon :: Name -> Q [Dec]
deriveAppCon name = do
  (TyConI (DataD _ _ _ _ [RecC con fields] _)) <- reify name

  let names = [mkName (nameBase n) | (n,_,_) <- fields]
      apps = go [|pure $(conE con)|] [[|unO $(varE n)|] | n <- names] where
        go l [] = l
        go l (r:rs) = go [|$l <*> $r|] rs

  [d|instance AppCon $(conT name) where
      appCon ($(conP con (map varP names))) = $apps
    |]

I use the type composition operator from the TypeCompose package to define a type-class that can "unwrap" a single applicative layer from a record type. I.e if you have a FooC (IO :. Maybe) you can turn it into a IO (FooC Maybe).

The deriveAppCon lets you automatically derive an instance for any basic record type.

{-# LANGUAGE TemplateHaskell #-}

import Control.Compose ((:.)(..))

import AppCon

data FooC f = FooC { x :: f Int, y :: f Text }
type Foo = FooC Maybe

deriveAppCon ''FooC

myfoo :: IO Foo
myfoo = appCon $ FooC
    { x = O $ someEnvInt "someX"
    , y = O $ someEnvText "someY"
    }

The O constructor from TypeCompose is used to wrap the function result IO (Maybe a) into a composite ((IO .: Maybe) a).

shang
  • 24,642
  • 3
  • 58
  • 86