Haskell: Using RankNTypes to fold a record constru

2019-07-06 12:17发布

import Data.ConfigFile

data Test = Test 
  { field1 :: Int
  , field2 :: Bool
  , field3 :: String
  } deriving (Show)

whatMyConfigLooksLike = 
    [ ("field1", "5")
    , ("field2", "True")
    , ("field3", "I am a string")
    ]

options = fst . unzip $ whatMyConfigLooksLike

readConfigFile = do
  rv <- runErrorT $ do 
    cp <- join . liftIO $ readfile emptyCP "theconfig.cfg"
    let printn = liftIO . putStrLn
        getn = get x "DEFAULT"
        x = cp
    printn "Loading configuration file..."
    -- I don't want to do the following
    one <- getn "field1"
    two <- getn "field2"
    three <- getn "field3"
    return $ Test one two three -- ...
    -- ... and so on because I have a data type with many fields

    -- I want to fold them onto the data constructor instead
    return $ foldl (\f s -> getn s >>= f) (Test) options
    -- but I think this doesn't type check because f's type is constantly changing?
  print rv

In the above code I have a lambda with a very polymorphic type foldl (\f s -> getn s >>= f). From what I can tell, this causes it to not typecheck in its following recursions.

I think that I can use the RankNTypes language extension for my purpose to define a polymorphic recursive type that can represent any partial application of a function and, hence, allow the function to typecheck. With experimentation, much trial and equal amounts of error, though, I have been unable to come up with anything which compiles.

I would be very grateful if somebody can show me how to implement the RankNTypes extension in terms of the example code above (or suggest alternatives). I'm using GHC 7.4.2.

2条回答
成全新的幸福
2楼-- · 2019-07-06 12:21

TL;DR: Generate your code for you using the module listed at the bottom under "Code Summary"

You can't bear to write all that boilerplate code. I can very much sympathise. There are other approaches, but we could use Template Haskell to generate the code we need.

If you're new to Template Haskell, you should have a look at the haskellwiki page.

First, let's turn on the Template Haskell extension, and import Control.Applicative to tidy the code up a bit:

{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Control.Applicative

What template haskell code should we generate?

And let's ask ghci to convert an appropriate expression for us. (I faked a getn function for convenience so I can use it in standalone code.)

*Main> :set -XTemplateHaskell
*Main> runQ [| Test <$> getn "field1" <*> getn "field2" <*> getn "field3" |]
InfixE (Just (InfixE (Just (InfixE (Just (ConE Main.Test)) (VarE Data.Functor.<$>) (Just (AppE (VarE Main.getn) (LitE (StringL "field1")))))) (VarE Control.Applicative.<*>) (Just (AppE (VarE Main.getn) (LitE (StringL "field2")))))) (VarE Control.Applicative.<*>) (Just (AppE (VarE Main.getn) (LitE (StringL "field3"))))

Woah! let's tidy that up a bit, and make it valid haskell code. Firstly note that an expression such as Data.Functor.<$> is actually of type Name. To get it we could do mkName "<$>", but string mangling is the ugliest sort of source code manipulation, so let's do '(<$>) instead, which generates the (fully qualified) name from the function:

whatWeWant = InfixE 
    (Just (InfixE 
             (Just (InfixE 
                      (Just (ConE 'Test)) 
                      (VarE '(<$>)) 
                      (Just (AppE (VarE 'getn) (LitE (StringL "field1")))))) 
             (VarE '(<*>)) 
             (Just (AppE (VarE 'getn) (LitE (StringL "field2")))))) 
    (VarE '(<*>)) 
    (Just (AppE (VarE 'getn) (LitE (StringL "field3"))))

The (hidden) beauty of this is that it's just a load of very similar expressions that we can fold together.

Generating the expressions we need

fieldExpressions :: Name -> [String] -> [Exp]
fieldExpressions getter = map $ \field -> AppE (VarE getter) (LitE (StringL field))

Let's use <<*>> as a sort of lift of <*> to glue expressions together with <*>:

(<<*>>) :: Exp -> Exp -> Exp
a <<*>> b = InfixE  (Just a)  (VarE '(<*>))  (Just b)

Now when we get the fields, we'll first apply the constructor via <$> to the first field, then we can use that as the base for a fold over the other fields.

getFields :: Name -> [Exp] -> Exp
getFields _ [] = error "getFields: empty field list"
getFields constructor (f:fs) = foldl (<<*>>) 
                               ( InfixE  (Just $ ConE constructor)  (VarE '(<$>))  (Just f) )
                               fs

A quick check:

*Main> whatWeWant == (getFields 'Test $ fieldExpressions 'getn ["field1","field2","field3"])
True

The stage restriction bites

We could test/use that in the same source file with

domything = do
   optionsRecord <- $(return $ getFields 'Test $ fieldExpressions 'getn ["field1","field2","field3"])
   print optionsRecord

except that you'll run into the rather inconvenient stage restriction:

GHC stage restriction: `getFields'
  is used in a top-level splice or annotation,
  and must be imported, not defined locally

That means that you'll have to define getFields etc in another module, and then import that into your main file where you can splice it in.

Code Summary

GetFields.hs:

{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Control.Applicative

module GetFields where

fieldExpressions :: Name -> [String] -> [Exp]
fieldExpressions getter = map $ \field -> AppE (VarE getter) (LitE (StringL field))

(<<*>>) :: Exp -> Exp -> Exp
a <<*>> b = InfixE  (Just a)  (VarE '(<*>))  (Just b)

getFields :: Name -> [Exp] -> Exp
getFields _ [] = error "getFields: empty field list"
getFields constructor (f:fs) = foldl (<<*>>) 
                               ( InfixE  (Just $ ConE constructor)  (VarE '(<$>))  (Just f) )
                               fs

Main.hs:

import GetFields
import Data.ConfigFile

...defs...

readConfigFile = do
  rv <- runErrorT $ do 
    cp <- join . liftIO $ readfile emptyCP "theconfig.cfg"
    let printn = liftIO . putStrLn
        getn = get x "DEFAULT"
        x = cp
    printn "Loading configuration file..."
    someoptions <- $(getFields 'Test $ fieldExpressions 'getn ["field" ++ show n| n<-[1..30]])
查看更多
叛逆
3楼-- · 2019-07-06 12:31

What you are trying to do is not possible. The typechecker does not know how many elements are in the list, and thus how many arguments you are trying to pass to the constructor. You do, but that is irrelevant in a statically checked language.

RankNTypes is not going to help because the root problem is not the type of your lambda (even if that is where the typechecker throws the error. The problem is with your accumulator: foldl has type (a -> b -> a) -> a -> [b] -> a; Note, in particular, that no matter how many extensions you throw at the typechecker, the accumulator must have the same type at each point in the fold. Test has type Int -> Bool -> String -> Test; its first partial application has type Bool -> String -> Test, and there is no way to unify those types.

If the rest of your program is well-typed, however, you should be able to use simply liftM3 Test (getn "field1") (getn "field2") (getn "field3") as your return, which is little more verbose and far clearer than what you were attempting.

查看更多
登录 后发表回答