Reputation: 333
I have a system with a long list of different functions. I would like the user to be able to pass data into these functions from a shell. If the data that they pass is of the wrong type, a error should be displayed when the function is executed.
Data needs to be stored in a general way, as the same type, so that it can be stored in lists before being passed into an exec function.
data Data = DInt Int | DBool Bool | DChar Char .....
Is there a way for a list of Data, to be passed into a function like such?
exec :: [Data] -> (wrapped up function) -> Either Error Data
If the function was expecting a Bool but an Int was found, an error is thrown etc.
The function would have to wrapped in some sort of structure to allow this application but I'm not sure if there's an easy way to achieve this kind of behaviour.
Thanks, second trying trying to write this so please ask for any clarification.
Upvotes: 2
Views: 397
Reputation: 64740
What I think you are asking for is entirely non-idiomatic. I'm going to present an answer that you should never use because if it is what you want then you are solving the problem the wrong way.
A Bad But Fun Solution
Overview: We will be constructing boxes - values of any type. These boxes will carry both the value and a type representation we can use for equality checks to ensure our function applications and return types are all correct. We then manually check the type representations (values that represent the types, which were lost at compile time) before applying the function. Remember the function and the argument types are opaque - they've been erased at compile time - so we need to use the sinful function unsafeCoerce
.
So to start with we need existential types, typeable and unsafe coerce:
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE TypeApplications #-}
import Data.Typeable
import Unsafe.Coerce
The Box is our existential:
data Box = forall a. Box (TypeRep, a)
If we were making a module with a safe API we'd want to make a smart constructor:
-- | 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)
Your exec
function now doesn't need to take a list of this ugly sum type (Data
) but can instead take a list of boxes and the function, in the form of a box, then apply each argument to the function one at a time to obtain the result. Notice the caller needs to statically know the return type - signified by the Proxy argument - or else we'd have to return a Box as the result which is pretty useless.
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!)
We can test the three outcomes simply:
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)
Yielding:
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."
EDIT: I should mention that Box
and this API is more educational and less concise than needed since you can use Data.Dynamic
. For example (I changed up the API too since proxy can be inferred):
{-# 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)
Upvotes: 4
Reputation: 50829
Here's one approach that uses type classes with one extension.
{-# LANGUAGE FlexibleInstances #-}
The idea is to define exec
within a Function
type class:
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
and then define a pair of instances for each Data
constructor, one to type-check and apply an argument of that type, recursively evaluating exec
to move on to the remaining arguments:
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"
and another to handle a "final value" of that type:
instance Function Int where
exec x [] = Right (DInt x)
exec _ _ = Left ExtraArgs
You need similar boilerplate for Bool
and Char
and all your other supported types. (Actually, much of this boilerplate can probably be removed with some helper functions and/or perhaps by introducing a second DataType
typeclass with Int
, Bool
, and Char
instances, but I haven't worked that out.)
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
and then:
> 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
>
Perhaps surprisingly, exec
itself wraps these functions into the same type, so you can write:
> let myFunctions = [exec f, exec g]
> :t myFunctions
myFunctions :: [[Data] -> Either Error Data]
> (myFunctions !! 0) [DInt 1, DInt 2]
Right (DInt 3)
>
which allows you to manipulate these functions as first class values of type [Data] -> Either Error [Data]
.
Upvotes: 1
Reputation: 900
readMaybe
is in the Text.Read
package. I would try to read an input, and if returns Nothing
try to parse another type. You must to keep an order to do so. For instance, first Int
, then Bool
, etc.
http://hackage.haskell.org/package/base-4.10.1.0/docs/Text-Read.html#v:readMaybe
Upvotes: 2