Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Applicative constructor for records

I want to generically create applicative constructors for haskell records in order to create a parser for the record.

Consider the record:

data Record = Record {i :: Int, f :: Float}

the constructor I want:

Record <$> pInt <*> pFloat

Parsers for basic types are given:

class Parseable a where
  getParser :: Parser a

instance Parseable Int where
  getParser = pInt

instance Parseable Float where
  getParser = pFloat

Are there any libraries that can already do this? Is it maybe possible to define getParser for a record? Thanks in advance.

like image 334
Maarten Avatar asked Jul 10 '12 14:07

Maarten


2 Answers

This can be done using, for instance, the regular library. Working with this library generally requires some language extensions:

{-# LANGUAGE FlexibleContexts     #-}
{-# LANGUAGE FlexibleInstances    #-}
{-# LANGUAGE TypeFamilies         #-}
{-# LANGUAGE TypeOperators        #-}
{-# LANGUAGE UndecidableInstances #-}

import Control.Applicative
import Generics.Regular

At least two of the most popular parser-combinator libraries come with an applicative-functor interface: see, for instance, uu-parsinglib and parsec, but to keep things easy, let's use simple list-of-successes parsers here.

newtype Parser a = Parser {runParser :: ReadS a}

instance Functor Parser where
  fmap f p = Parser $ \s -> [(f x, s') | (x, s') <- runParser p s]

instance Applicative Parser where
  pure x  = Parser $ \s -> [(x, s)]
  p <*> q = Parser $ \s ->
    [(f x, s'') | (f, s') <- runParser p s, (x, s'') <- runParser q s']

instance Alternative Parser where
  empty   = Parser $ \_ -> []
  p <|> q = Parser $ \s -> runParser p s ++ runParser q s

(Note that type ReadS a = String -> [(a, String)].)

pSym :: Char -> Parser Char
pSym c = Parser $ \s -> case s of
  (c' : s') | c == c' -> [(c', s')]
  _                   -> []

pInt :: Parser Int
pInt = Parser reads

pFloat :: Parser Float
pFloat = Parser reads

Straightforwardly, we have:

class Parseable a where
  getParser :: Parser a

instance Parseable Int where
  getParser = pInt

instance Parseable Float where
  getParser = pFloat

And, for your record type, as desired:

data Record = Record {i :: Int, f :: Float}

instance Parseable Record where
  getParser = Record <$> pInt <* pSym ' ' <*> pFloat

Now, how do we generically generate such a parser?

First, we define the so-called pattern functor of Record (see the documentation of regular for details):

type instance PF Record = K Int :*: K Float

Then, we make Record an instance of the type class Regular:

instance Regular Record where
  from (Record n r) = K n :*: K r
  to (K n :*: K r)  = Record n r

Next, we define a generic parser:

class ParseableF f where
  getParserF :: Parser a -> Parser (f a)

instance ParseableF (K Int) where
  getParserF _ = K <$> pInt

instance ParseableF (K Float) where
  getParserF _ = K <$> pFloat

instance (ParseableF f, ParseableF g) => ParseableF (f :*: g) where
  getParserF p = (:*:) <$> getParserF p <* pSym ' ' <*> getParserF p

(To cover all regular types, you will have to provide some more instances, but these will do for your example.)

Now, we can demonstrate that every type in the class Regular (given a ParseableF instance for its pattern functor) comes with a parser:

instance (Regular a, ParseableF (PF a)) => Parseable a where
  getParser = to <$> getParserF getParser

Let's take it for a spin. Drop the original instances of Parseable (i.e., the ones for Int, Float, and of course Record) and only keep the single generic instance. Here we go:

> runParser (getParser :: Parser Record) "42 3.14"
[(Record {i = 42, f = 3.14},"")]

Note: this is just a very basic example of how to derive generic parsers using the regular library. The library itself comes with a generic list-of-successes parser that does particularly nice things with records. You may want to check that one out first. Moreover, the library comes with Template Haskell support so that instances of Regular can be derived automatically. These instances include special structure types for record labels, so that you can have your generic functions treat record types really fancy. Check out the docs.

like image 59
Stefan Holdermans Avatar answered Sep 27 '22 23:09

Stefan Holdermans


As much as I like the regular package, I want to point out that since ghc-7.2 the GHC has built-in support for deriving generic representation types, so that you do not have to rely on Template Haskell to do that.

Changes compared to the solution suggested by dblhelix are the following. You need slightly different flags and modules imported:

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeOperators #-}

import Control.Applicative
import GHC.Generics

You still define Parser and its instances as above. You need to derive the class Generic for your Record type:

data Record = Record { i :: Int, f :: Float }
  deriving (Generic, Show)

The class Generic is very similar to the class Regular. You don't have to define PF or an instance of Regular now.

Instead of ParseableF, we define a class Parseable' that's very similar in style, yet ever so slightly different:

class Parseable' f where
  getParser' :: Parser (f a)

-- covers base types such as Int and Float:
instance Parseable a => Parseable' (K1 m a) where
  getParser' = K1 <$> getParser

-- covers types with a sequence of fields (record types):
instance (Parseable' f, Parseable' g) => Parseable' (f :*: g) where
  getParser' = (:*:) <$> getParser' <* pSym ' ' <*> getParser'

-- ignores meta-information such as constructor names or field labels:
instance Parseable' f => Parseable' (M1 m l f) where
  getParser' = M1 <$> getParser'

Finally, for Parseable, we define a generic default method:

class Parseable a where
  getParser :: Parser a
  default getParser :: (Generic a, Parseable' (Rep a)) => Parser a
  getParser = to <$> getParser'

instance Parseable Int where
  getParser = pInt

instance Parseable Float where
  getParser = pFloat

Now, making the Record type parseable is as simple as providing an empty instance declaration:

instance Parseable Record

The example works as previously:

> runParser (getParser :: Parser Record) "42 3.14"
[(Record {i = 42, f = 3.14},"")]
like image 45
kosmikus Avatar answered Sep 28 '22 00:09

kosmikus