请考虑以下类型签名:

data Foo x = Foo {
    name :: String
  , reader :: String -> x
}

instance Functor Foo where
  fmap f (Foo n r) = Foo n $ f . r

现在,我展示了从Foooptparse-applicativeParser类型的自然转换:
import qualified Options.Applicative as CL

mkParser :: Foo a -> CL.Parser a
mkParser (Foo n _) = CL.option CL.disabled ( CL.long n )

(好吧,这没什么用,但将用于讨论)。

现在,我将Bar替换为Foo的免费替代函子:
type Bar a = Alt Foo a

鉴于这是一个免费的函子,我应该能够将mkParser提升为从BarParser的自然转换:
foo :: String -> (String -> x) -> Bar x
foo n r = liftAlt $ Foo n r

myFoo :: Bar [String]
myFoo = many $ foo "Hello" (\_ -> "Hello")

clFoo :: CL.Parser [String]
clFoo = runAlt mkParser $ myFoo

确实,这可行,并且给了我Parser。但是,这是一个非常无用的方法,因为尝试对其执行很多操作会导致无限循环。例如,如果我尝试描述一下:
CL.cmdDesc clFoo
> Chunk {unChunk =

并挂起直到被打断。

原因似乎是optparse-applicativemany的定义中的some cheats:它在幕后使用了monadic解析。

我在这里做错什么了吗?鉴于此,我不知道如何以这种方式构造解析器。有任何想法吗?

最佳答案

如注释中所指出的,您必须显式处理many。从 Earley 复制的方法:

#!/usr/bin/env stack
-- stack --resolver=lts-5.3 runghc --package optparse-applicative
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}

import Control.Applicative
import qualified Options.Applicative as CL
import qualified Options.Applicative.Help.Core as CL

data Alt f a where
  Pure   :: a                             -> Alt f a
  Ap     :: f a       -> Alt f (a -> b)   -> Alt f b
  Alt    :: [Alt f a] -> Alt f (a -> b)   -> Alt f b
  Many   :: Alt f a   -> Alt f ([a] -> b) -> Alt f b

instance Functor (Alt f) where
  fmap f (Pure x)   = Pure $ f x
  fmap f (Ap x g)   = Ap x $ fmap (f .) g
  fmap f (Alt x g)  = Alt x $ fmap (f .) g
  fmap f (Many x g) = Many x $ fmap (f .) g

instance Applicative (Alt f) where
  pure = Pure

  Pure f   <*> y = fmap f y
  Ap x f   <*> y = Ap x $ flip <$> f <*> y
  Alt xs f <*> y = Alt xs $ flip <$> f <*> y
  Many x f <*> y = Many x $ flip <$> f <*> y

instance Alternative (Alt f) where
  empty = Alt [] (pure id)
  a <|> b = Alt [a, b] (pure id)
  many x  = Many x (pure id)

-- | Given a natural transformation from @f@ to @g@, this gives a canonical monoidal natural transformation from @'Alt' f@ to @g@.
runAlt :: forall f g a. Alternative g => (forall x. f x -> g x) -> Alt f a -> g a
runAlt u = go where
    go :: forall b. Alt f b -> g b
    go (Pure x)    = pure x
    go (Ap x f)    = flip id <$> u x                           <*> go f
    go (Alt xs f)  = flip id <$> foldr (<|>) empty (map go xs) <*> go f
    go (Many x f)  = flip id <$> many (go x)                   <*> go f

-- | A version of 'lift' that can be used with just a 'Functor' for @f@.
liftAlt :: (Functor f) => f a -> Alt f a
liftAlt x = Ap x (Pure id)

mkParser :: Foo a -> CL.Parser a
mkParser (Foo n r) = CL.option (CL.eitherReader $ Right . r) ( CL.long n CL.<> CL.help n )

data Foo x = Foo {
    name :: String
  , reader :: String -> x
}

instance Functor Foo where
  fmap f (Foo n r) = Foo n $ f . r

type Bar a = Alt Foo a

foo :: String -> (String -> x) -> Bar x
foo n r = liftAlt $ Foo n r

myFoo :: Bar [String]
myFoo = many $ foo "Hello" (\_ -> "Hello")

clFoo :: CL.Parser [String]
clFoo = runAlt mkParser $ myFoo

main :: IO ()
main = do
  print $ CL.cmdDesc clFoo
  print $ CL.cmdDesc $ mkParser (Foo "Hello" $ \_ -> "Hello")

关于haskell - 从免费的替代仿函数生成optparse适用的解析器,我们在Stack Overflow上找到一个类似的问题:https://stackoverflow.com/questions/26718443/

10-12 16:32