2017-12-27 841 views
2

我有一个系统,其中包含很多不同的功能。我希望用户 能够将数据从shell传递到这些函数中。如果它们传递的数据类型错误,则在执行该功能时应显示错误。Haskell:函数在包装数据上的应用

数据需要以一般方式存储为相同类型,以便在传递给exec函数之前可以将其存储在列表中。

data Data = DInt Int | DBool Bool | DChar Char ..... 

有没有一种方法可以将数据列表传递到像这样的函数中?

exec :: [Data] -> (wrapped up function) -> Either Error Data 

如果函数期待一个布尔而是一个Int发现,则会引发错误等

功能必须包裹在某种结构允许该应用程序,但我不确定是否有简单的方法来实现这种行为。

谢谢,第二次试图写这个,所以请要求澄清。

+0

您是否熟悉'Data.Dynamic'? –

回答

2

readMaybe位于Text.Read包中。我会尝试读取输入,如果返回Nothing尝试解析另一种类型。你必须保持命令这样做。例如,第一Int,然后Bool

http://hackage.haskell.org/package/base-4.10.1.0/docs/Text-Read.html#v:readMaybe

+1

该提议使用'String'作为穷人的'Data.Dynamic.Dynamic'并解析('readMaybe')来代替显式的'TypeRep'。如果数据是以字符串形式开始的,那么这是一个很好的策略,但如果数据实际上是一个Haskell值,那么调用'show'只是为了统一类型,这有点笨拙。 –

4

认为你所要求的是完全不地道。我将提出一个你永远不应该使用的答案,因为如果它是你想要的,那么你正在以错误的方式解决问题。

一个坏的,但有趣的解决方案

概述:我们将构建盒 - 的任何类型的值。这些框将携带我们可用于相等性检查的值和类型表示,以确保我们的函数应用程序和返回类型都是正确的。然后,我们在应用函数之前手动检查类型表示(表示类型的值,这些值在编译时丢失)。记住函数和参数类型是不透明的 - 它们在编译时被擦除 - 所以我们需要使用有罪功能unsafeCoerce

所以先从我们需要生存类型,分型和不安全的要挟:

{-# LANGUAGE ExistentialQuantification #-} 
{-# LANGUAGE TypeApplications #-} 
import Data.Typeable 
import Unsafe.Coerce 

这个盒子是我们的生存:

data Box = forall a. Box (TypeRep, a) 

如果我们做一个模块提供一个安全的API,我们” d想做一个聪明的构造函数:

-- | Convert a type into a "box" of the value and the value's type. 
mkBox :: Typeable a => a -> Box 
mkBox a = Box (typeOf a, a) 

您的exec函数现在不需要获取这个丑陋的总和类型的列表(Data),而是可以以框的形式取出框和函数的列表,然后将每个参数应用于函数,以获得结果。注意,调用者需要静态地知道返回类型 - 由Proxy参数表示 - 否则我们必须返回一个Box,因为结果很无用。

exec :: Typeable a 
    => [Box] --^Arguments 
    -> Box --^Function 
    -> Proxy a 
    -> Either String a 
exec [] (Box (fTy,f)) p 
    | fTy == typeRep p = Right $ unsafeCoerce f 
    -- ^^ The function is fully applied. If it is the type expected 
    -- by the caller then we can return that value. 
    | otherwise  = Left "Final value does not match proxy type." 
exec ((Box (aTy,a)):as) (Box (fTy,f)) p 
    | Just appliedTy <- funResultTy fTy aTy = exec as (Box (appliedTy, (unsafeCoerce f) (unsafeCoerce a))) p 
    -- ^^ There is at least one more argument 
    | otherwise = Left "Some argument was the wrong type. XXX we can thread the arg number through if desired" 
    -- ^^ The function expected a different argument type _or_ it was fully applied (too many argument supplied!) 

我们可以测试三种结果只是:

main :: IO() 
main = 
    do print $ exec [mkBox (1::Int), mkBox (2::Int)] (mkBox ((+) :: Int -> Int -> Int)) (Proxy @Int) 
    print $ exec [mkBox (1::Int)] (mkBox (last :: [Int] -> Int)) (Proxy @Int) 
    print $ exec [mkBox (1::Int)] (mkBox (id :: Int -> Int)) (Proxy @Double) 

产量:

Right 3 
Left "Some argument was the wrong type. XXX we can thread the arg number through if desired" 
Left "Final value does not match proxy type." 

编辑:我应该指出,Box这个API是更多的教育,比必要的,因为不够简明您可以使用Data.Dynamic。例如(因为代理可以推断,我也更改了API):

{-# LANGUAGE ExistentialQuantification #-} 
{-# LANGUAGE GADTs #-} 
import Data.Dynamic 
import Type.Reflection 

type Box = Dynamic 

-- | Convert a type into a "box" of the value and the 
-- value's type. 
mkBox :: Typeable a => a -> Box 
mkBox = toDyn 

exec :: Typeable a 
    => [Box] --^Arguments 
    -> Box --^Function 
    -> Either String a 
exec [] f = case fromDynamic f of 
       Just x -> Right x 
       Nothing -> Left "Final type did not match proxy" 
exec (a:as) f 
    | Just applied <- dynApply f a = exec as applied 
    | otherwise = Left "Some argument was the wrong type. XXX we can thread the arg number through if desired" 


main :: IO() 
main = 
    do print (exec [mkBox (1::Int), mkBox (2::Int)] (mkBox ((+) :: Int -> Int -> Int)) :: Either String Int) 
    print (exec [mkBox (1::Int)] (mkBox (last :: [Int] -> Int)) :: Either String Int) 
    print (exec [mkBox (1::Int)] (mkBox (id :: Int -> Int)) :: Either String Double) 
+0

你为什么使用'unsafeCoerce'?经典的“盒子”是“数据盒子=全部”。 Typeable a => Box a',它可让您使用'cast','eqT'或'gcast'正确完成工作。是的,这些最终建立在'unsafeCoerce'(在Data.Typeable的实现中),但没有一个应该关心用户。如果您喜欢,可以使用新的“Type.Reflection”正确编写更像您的盒子样式。 – dfeuer

+0

事实上,我在使用动态的版本中隐式地使用反射模块。 –

1

以下是一种使用带有一个扩展名的类型类的方法。

{-# LANGUAGE FlexibleInstances #-} 

的想法是一个Function类型的类中定义exec

data Data = DInt Int | DBool Bool | DChar Char deriving (Show) 
data Error = TypeError String Data | MissingArg String | ExtraArgs 
      deriving (Show) 

class Function a where 
    exec :: a -> [Data] -> Either Error Data 

,然后限定一对实例的每个Data构造函数,一个类型检查并应用类型的参数,递归评估exec以继续讨论其余参数:

instance Function r => Function (Int -> r) where 
    exec f (DInt x : xs) = exec (f x) xs 
    exec _ ( y : xs) = Left $ TypeError "DInt" y 
    exec _ []   = Left $ MissingArg "DInt" 

和另一个要汉DLE该类型的“终值”:

instance Function Int where 
    exec x [] = Right (DInt x) 
    exec _ _ = Left ExtraArgs 

您需要类似的样板的BoolChar和所有其他支持的类型。 (其实,这多少样板大概可以用一些辅助功能和/或可能通过引入第二DataType类型类与IntBoolChar实例中删除,但我没有工作了这一点。)

instance Function r => Function (Bool -> r) where 
    exec f (DBool x : xs) = exec (f x) xs 
    exec _ (  y : xs) = Left $ TypeError "DBool" y 
    exec _ []    = Left $ MissingArg "DBool" 
instance Function Bool where 
    exec x [] = Right (DBool x) 
    exec _ _ = Left ExtraArgs 

instance Function r => Function (Char -> r) where 
    exec f (DChar x : xs) = exec (f x) xs 
    exec _ (  y : xs) = Left $ TypeError "DChar" y 
    exec _ []    = Left $ MissingArg "DChar" 
instance Function Char where 
    exec x [] = Right (DChar x) 
    exec _ _ = Left ExtraArgs 

然后:

> exec f [DInt 1, DInt 2] 
Right (DInt 3) 
> exec g [DBool True, DInt 1, DInt 0] 
Right (DInt 1) 
> exec f [DInt 1, DChar 'a'] 
Left (TypeError "DInt" (DChar 'a')) 
> exec f [DInt 1] 
Left (MissingArg "DInt") 
> exec f [DInt 1, DInt 2, DInt 3] 
Left ExtraArgs 
> 

也许令人惊讶,exec本身包装这些功能整合到同一类型的,所以你可以写:

> let myFunctions = [exec f, exec g] 
> :t myFunctions 
myFunctions :: [[Data] -> Either Error Data] 
> (myFunctions !! 0) [DInt 1, DInt 2] 
Right (DInt 3) 
> 

它允许您操作这些函数作为[Data] -> Either Error [Data]类型的第一类值。

+0

如果你不想要,你不需要使用'FlexibleInstances'。您可以添加一个辅助类'Arg a',其中exec':: Function r =>(a - > r) - > [Data] - > Error Data',然后使用实例'instance(Arg a,Function r )=>函数(a - > r)其中exec = exec''。 – dfeuer