Referring to type in instance declaration - haskell

I'm trying to use undefined to get value of type constant (something like sizeOf in storable).
module Main where
class MyClass a where
typeConst :: a -> String
-- ^ Argument is ignored
class TryRead a where
tryRead :: String -> Maybe a
newtype ByLen a = ByLen a
-- | Make all types under ByLen readable, if their typeConst's are longer then 3 characters
instance (Read a, MyClass a) => TryRead (ByLen a) where
tryRead = if len > 3
then Just . ByLen . read
else const Nothing
where
len = length $ typeConst (undefined :: a)
instance MyClass Int where
typeConst = const "moreThan3"
main :: IO ()
main = go (tryRead "214234" :: Maybe (ByLen Int))
where
go Nothing = print "Nothing :("
go (Just (ByLen i)) = print i
However, this gives an error:
Could not deduce (MyClass a0) arising from a use of ‘typeConst’
from the context (Read a, MyClass a)
bound by the instance declaration at src/Main.hs:13:10-49
The type variable ‘a0’ is ambiguous
Note: there is a potential instance available:
instance MyClass Int -- Defined at src/Main.hs:20:10
In the second argument of ‘($)’, namely
‘typeConst (undefined :: a)’
In the expression: length $ typeConst (undefined :: a)
In an equation for ‘len’: len = length $ typeConst (undefined :: a)
I don't understand what problem with type deducing is there, considering I specified type for typeConst argument explicitly as a type variable, which is bound by MyClass a, so it should in my mind have no problems applying to typeConst function.

You need ScopedTypeVaribales extension to be enabled for this to work either through a ghc flag -XScopedTypeVariables or through a pragma at the top of the file:
{-# LANGUAGE ScopedTypeVariables #-}
If it used within a class instance, nothing special needs to be done, because type variables from the head of the class are already in the scope, but if you would like to use it in simple top level function you will need an explicit forall in the type signature.

Related

Reify existential instance type parameter

I've got some code like this:
{-# LANGUAGE AllowAmbiguousTypes #-}
module Foo where
import Data.Proxy
class Foo x y
class Bar x y
class Baz x y
where
baz :: Proxy x -> Proxy y -> ()
instance (Foo a v, Bar b v) => Baz a b
where
baz _ _ = ()
instance Foo String String
instance Bar Int String
Now I actually want to use that Baz instance, so I write:
test :: Proxy String -> Proxy Int -> ()
test = baz
But of course there is an ambiguous "existential" v type parameter that I have not yet fixed to String (and there's no fundeps), so I get:
[typecheck] [E] /tmp/foo/src/Main.hs:20:8: error:
• Ambiguous type variable ‘v1’ arising from a use of ‘baz’
prevents the constraint ‘(Foo [Char] v1)’ from being solved.
Probable fix: use a type annotation to specify what ‘k1’,
‘v1’ should be.
These potential instance exist:
one instance involving out-of-scope types
(use -fprint-potential-instances to see them all)
• In the expression: baz
In an equation for ‘test’: test = baz
But how can I actually fix that type variable? I can't see a way to fix it using visible type application, because for example the following doesn't work:
test2 :: Proxy String -> Proxy Int -> ()
test2 = baz #String #Int #String -- is there some variation of this that would work?
I also can't see a way to use an explicit type annotation to fix that type parameter. Have I written an instance that is impossible to actually use?
It is indeed impossible to use that instance. When you call baz, you can supply a and b, but not v. v would have to be determined by some combination of superclass and instance constraints, and it is not.
You should be able to patch this up various places. Try either
instance s ~ String => Foo String s
or
instance s ~ String => Bar Int s
for example.

How to tell whether variable is a certain data in Haskell?

Edit: This class instance of QWhere fails when it's passed input like this: >qWhere fly john even though fly is type Argument -> Argument -> Predicate and john is type Argument.
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
data Argument = Argument { ttype :: Type, value :: String } deriving (Show, Eq)
data Predicate = Predicate { lemma :: String, arguments :: [Argument] } deriving (Show, Eq)
class Fly a b where
fly :: a -> b -> Predicate
instance Fly Argument Argument where
fly x y = Predicate { lemma = "fly", arguments = [x, y] }
instance Fly Argument Predicate where
fly x y = Predicate { lemma = "fly", arguments = [x, arguments y !! 0] }
class QWhere a b where
qWhere :: a -> b -> String
instance QWhere (Argument -> Argument -> Predicate) Argument where
qWhere x y = "hi"
This is the output from the ghci:
No instance for (QWhere (a0 -> b0 -> Predicate) Argument)
arising from a use of ‘qWhere’
The type variables ‘a0’, ‘b0’ are ambiguous
Note: there is a potential instance available:
instance QWhere (Argument -> Argument -> Predicate) Argument
-- Defined at new_context.hs:116:10
In the expression: qWhere fly john
In an equation for ‘it’: it = qWhere fly john
No instance for (Fly a0 b0) arising from a use of ‘fly’
The type variables ‘a0’, ‘b0’ are ambiguous
Note: there are several potential instances:
instance Fly Argument Predicate
-- Defined at new_context.hs:110:10
instance Fly Argument Argument
-- Defined at new_context.hs:107:10
In the first argument of ‘qWhere’, namely ‘fly’
In the expression: qWhere fly john
In an equation for ‘it’: it = qWhere fly john
These questions are relevant, but none of the answers have solved my problem.
(1) Checking for a particular data constructor
(2) Test if Haskell variable matches user-defined data type option
And some internet sources which should address this question but I could not find the solution from:
(3) https://www.haskell.org/haskellwiki/Determining_the_type_of_an_expression
(4) http://okmij.org/ftp/Haskell/typeEQ.html
My problem: I have two Haskell data types defined. I am given an input and I need to determine if it belongs to data type A or data type B.
Here is the data types definition:
data Argument = Argument { ttype :: Type, value :: String } deriving (Show, Eq)
data Predicate = Predicate { lemma :: String, arguments :: [Argument] } deriving (Show, Eq)
I need a function which returns true/false if a variable is a data type Argument or Predicate.
I attempted to follow the answers of both SO questions, but only got complaints from the ghci compiler:
--checks if a variable is of data type Argument
--this does not compile (from question (2))
isArgument :: a -> Bool
isArgument (Argument _) = True
isArgument _ = False
--from question (1), also fails
isArgument :: a -> String
isArgument value =
case token of
Argument arg -> "is argument"
Predicate p -> "is predicate"
The sort of dynamic typing you are trying to do is very rarely used in Haskell. If you want to write functions that can take values of both Predicate and Argument there are at least two idiomatic ways depending on your exact use-case.
The first is to overload the function using type-classes. E.g.
class IsArgument a where
isArgument :: a -> Bool
instance IsArgument Argument where
isArgument _ = True
instance IsArgument Predicate where
isArgument _ = False
The second is to use some sum-type such as Either Predicate Argument or a custom sum-type such as:
data Expr = ArgumentExpr Argument | PredicateExpr Predicate
isArgument :: Expr -> Bool
isArgument (ArgumentExpr _) = True
isArgument _ = False
You can also make Argument and Predicate constructors of the same type, but then of course you lose the type safety of treating them as separate types. You can circumvent this by using a GADT and tagging the constructors with a phantom type but this gets into the slightly more advanced type extensions that GHC offers:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
data ExprType = Argument | Predicate
data Expr t where
ArgumentExpr :: { ttype :: Type, value :: String } -> Expr Argument
PredicateExpr :: { lemma :: String, arguments :: [Expr Argument] } -> Expr Predicate
deriving instance Show (Expr t)
deriving instance Eq (Expr t)
isArgument :: Expr t -> Bool
isArgument (ArgumentExpr {}) = True
isArgument _ = False
Now arguments and predicates are constructors of the same type but you can limit the values to a specific constructor by using the type parameter as is done in arguments :: [Expr Argument] but you can also just accept any expression using the type Expr t as in isArgument.
If you really really need run-time polymorphism, it can be achieved using the Typeable type-class which enables you to get runtime type information and do type-casts on opaque, generic types.
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Typeable
data Argument = Argument { ttype :: Type, value :: String } deriving (Show, Eq, Typeable)
data Predicate = Predicate { lemma :: String, arguments :: [Argument] } deriving (Show, Eq, Typeable)
isArgument :: Typeable a => a -> Bool
isArgument a = case cast a of
Just (Argument {}) -> True
_ -> False
The function cast tries to convert any Typeable a => a value into some known type and returns a Just value if the type-cast succeeds and Nothing if it fails.
You can do what you want by making Argument and Predicate part of the same type....
data LogicElement = Argument { ttype :: Type, value :: String } |
Predicate { lemma :: String, arguments :: [LogicElement] } deriving (Show, Eq)
While it is possible to define a function of type (a->Bool), it is unusual, and generally implies that the value being input will be ignored (ie- how can you do anything to something if you don't even know what it is? You pretty much can only apply other (a->b) functions on it).
In the particular example, you compiler will complain at the following
isArgument (Argument _) = True
because the pattern implicitly implies that the input argument must be type Argument, whereas the signature you gave was undefined type a.
When you say that isArgument has type a -> Bool, you're saying that it can take any, or rather every possible a, not just certain ones. There are a few solutions to this, though. My preference would be that for simple alternatives, just use Either:
import Data.Either
isArgument :: Either Argument Predicate -> Bool
isArgument = isLeft
Or
-- Note the use of {} instead of _, the {} expands to all fields in a record
-- the _ only would have taken the place of the ttype field, although you could have
-- (Argument _ _) to capture both fields of the Argument constructor
isArgument :: Either Argument Predicate -> Bool
isArgument (Left (Argument {})) = True
isArgument _ = False
Although, the only use of this sort of function would be when you aren't sure which data type you have, and a value in Haskell can't be ambiguously typed. It would be equivalent to if you had in Java/C/C++/C# something like
if (some_condition) {
x = "a string";
} else {
x = 5;
}
These are statically typed languages, a variable can't take on values of two different types. The same holds in Haskell. If you wanted to give a type to a variable that could take on two different values, you'd have to write a container for it. The Either container in Haskell is pre-defined for this purpose.

Returning an instance of a class in a Haskell Function [duplicate]

This question already has answers here:
Return specific type within Haskell
(3 answers)
Closed 8 years ago.
If the return of a function is a class ClassA, is it possible to return in such function any instance of ClassA? Ex: someFunction :: (ClassA a) => String -> a
So, why this function below does not work? Note that String is an instance of Eq
getAnyEq :: (Eq a) => String -> a
getAnyEq input |input == "1" = "something"
|otherwise = "other"
The error that occurs is:
Could not deduce (a ~ [Char])
from the context (Eq a)
bound by the type signature for getAnyEq :: Eq a => String -> a
at src/InterceptorRegistry.hs:11:13-33
`a' is a rigid type variable bound by
the type signature for getAnyEq :: Eq a => String -> a
at src/InterceptorRegistry.hs:11:13
I've tried to find this exact explanation on Internet resources but i did not find...could you show me some?
The type Eq a => a does not mean "A type which implements Eq", but rather "Any type that implements Eq. For example, if you implement your function using undefined:
getAnyEq :: (Eq a) => String -> a
getAnyEq str = undefined
The following functions compile correctly (although will crash with a undefined error at runtime):
x,y,z :: Bool
x = getAnyEq "test" == "hello"
y = getAnyEq "test" == [Just (Right True)]
z = getAnyEq "test" == ("this", "sss")
It isn't possible to give a decent implementation of your function, as there is no way of generating the value for the result.
A function that returns a type variable only makes sense when the type variable has an instance of a class which contains a function that returns the value. Eg consider the Num class:
class (Eq a, Show a) => Num a where
(+) :: a -> a -> a
(*) :: a -> a -> a
(-) :: a -> a -> a
negate :: a -> a
abs :: a -> a
signum :: a -> a
fromInteger :: Integer -> a
(note I was testing this on a pretty old version of ghc, your Num may not have Eq or Show constraints).
The function fromInteger returns an a (without needed an a as input), so we can get an a from that type class. The other functions can be used once you have a value. So the following function works:
getANum:: (Num a) => String -> a
getANum "zero" = fromInteger 0
getANum "asdf" = fromInteger 46
getANum _ = fromInteger 1
> getANum "asdf"
46
Note that as a literal integer is effectively parsed as fromInteger <num>, the fromInteger function calls in the above function aren't actually necessary. I just included them to show how it works.
Other common type classes which can be used to retrieve a value are:
Monad (using return)
Applicative (using pure)
Monoid (using mempty)
Read (using read or any other of its other functions)
In addition to #David Miani's wonderful answer, I'd also add that every function type declaration in standard Haskell type system implies a forall (or ∀) quantifier:
getAnyEq :: (Eq a) => String -> a
is semantically equivalent to
getAnyEq :: forall a . (Eq a) => String -> a
which you can try with the {-# LANGUAGE ExplicitForall #-} extension. That means, literally, that for each type a constrained with the type class Eq there is a function getAnyEq with the given type. However, you propose the definition for a single type (which is String) only, not forall.
I suggest that your definition would be valid with another quantifier, ∃:
getAnyEq :: exists a . (Eq a) => String -> a
It's not implemented by the GHC, but for example the obsolete UHC (Utrecht Haskell Compiler) supports it. Unfortunately, I can't currently try it.
After reading the answers above and the related topic linked on the top of this page, i've concluded that the solution is the using of Existentially Quantified Types.
So, the solution to my getAnyEq function is:
{-# LANGUAGE ExistentialQuantification #-}
data ShowEq = forall s. Eq s => SE s
getAnyEq :: String -> ShowEq
getAnyEq input |input == "1" = SE "ds"
|otherwise = SE "ss"
A very useful link that explains these types is: http://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types

Can't properly define transformation from universal type, that defined with GADT

I've defined an universal data type that can contain anything (well, with current implementation not totally anything)!
Here it is (complete code):
{-#LANGUAGE NoMonomorphismRestriction#-}
{-#LANGUAGE GADTs#-}
{-#LANGUAGE StandaloneDeriving#-}
data AnyT where
Any :: (Show a, Read a) => a -> AnyT
readAnyT :: (Read a, Show a) => (String -> a) -> String -> AnyT
readAnyT readFun str = Any $ readFun str
showAnyT :: AnyT -> String
showAnyT (Any thing) = show thing
deriving instance Show AnyT --Just for convinience!
a = [Any "Hahaha", Any 123]
And I can play with it in console:
*Main> a
[Any "Hahaha",Any 123]
it :: [AnyT]
*Main> readAnyT (read::String->Float) "134"
Any 134.0
it :: AnyT
*Main> showAnyT $ Any 125
"125"
it :: String
Well, I have it, but I need to process it somehow. For example, let's define transformation functions (functions definition, add to previous code):
toAnyT :: (Show a, Read a) => a -> AnyT -- Rather useless
toAnyT a = Any a
fromAny :: AnyT -> a
fromAny (Any thing) = thing
And there is the problem! the fromAny definition from previous code is incorrect! And I don't know how to make it correct. I get the error in GHCi:
2.hs:18:23:
Could not deduce (a ~ a1)
from the context (Show a1, Read a1)
bound by a pattern with constructor
Any :: forall a. (Show a, Read a) => a -> AnyT,
in an equation for `fromAny'
at 2.hs:18:10-18
`a' is a rigid type variable bound by
the type signature for fromAny :: AnyT -> a at 2.hs:17:12
`a1' is a rigid type variable bound by
a pattern with constructor
Any :: forall a. (Show a, Read a) => a -> AnyT,
in an equation for `fromAny'
at 2.hs:18:10
In the expression: thing
In an equation for `fromAny': fromAny (Any thing) = thing
Failed, modules loaded: none.
I tried some other ways that giving errors too.
I have rather bad solution for this: defining necessary functions via showAnyT and read (replace previous function definitions):
toAnyT :: (Show a, Read a) => a -> AnyT -- Rather useless
toAnyT a = Any a
fromAny :: Read a => AnyT -> a
fromAny thing = read (showAnyT thing)
Yes, it's work. I can play with it:
*Main> fromAny $ Any 1352 ::Float
1352.0
it :: Float
*Main> fromAny $ Any 1352 ::Int
1352
it :: Int
*Main> fromAny $ Any "Haha" ::String
"Haha"
it :: String
But I think it's bad, because it uses string to transform.
Could you please help me to find neat and good solution?
First a disclaimer: I don't know the whole context of the problem you are trying to solve, but the first impression I get is that this kind of use of existentials is the wrong tool for the job and you might be trying to implement some code pattern that is common in object-oriented languaged but a poor fit for Haskell.
That said, existential types like the one you have here are usually like black holes where once you put something in, the type information is lost forever and you can't cast the value back to its original type. However, you can operate on existential values via typeclasses (as you've done with Show and Read) so you can use the typeclass Typeable to retain the original type information:
import Data.Typeable
data AnyT where
Any :: (Show a, Read a, Typeable a) => a -> AnyT
Now you can implement all the functions you have, as long as you add the new constraint to them as well:
readAnyT :: (Read a, Show a, Typeable a) => (String -> a) -> String -> AnyT
readAnyT readFun str = Any $ readFun str
showAnyT :: AnyT -> String
showAnyT (Any thing) = show thing
toAnyT :: (Show a, Read a, Typeable a) => a -> AnyT -- Rather useless
toAnyT a = Any a
fromAny can be implemented as returning a Maybe a (since you cannot be sure if the value you are getting out is of the type you are expecting).
fromAny :: Typeable a => AnyT -> Maybe a
fromAny (Any thing) = cast thing
You're using GADTs to create an existential data type. The type a in the constructor existed, but there's no way to recover it. The only information available to you is that it has Show and Read instances. The exact type is forgotten, because that's what your constructor's type instructs the type system to do. "Make sure this type has the proper instances, then forget what it is."
There is one function you've missed, by the way:
readLike :: String -> AnyT -> AnyT
readLike s (Any a) = Any $ read s `asTypeOf` a
Within the context of the pattern match, the compiler knows that whatever type a has, there is a Read instance, and it can apply that instance. Even though it's not sure what type a is. But all it can do with it is either show it, or read strings as the same type as it.
What you have is something called Existential type. If you follow that link than you will find that in this pattern the only way to work with the "data" inside the container type is to use type classes.
In your current example you mentioned that a should have Read and Show instances and that means only the functions in these type classes can be used on a and nothing else and if you want to support some more operations on a then it should be constrained with the required type class.
Think it like this: You can put anything in a box. Now when you extract something out of that box you have no way to specify what you will get out of it as you can put anything inside it. Now if you say that you can put any eatable inside this box, then you are sure that when you pick something from this box it will be eatable.

Haskell: how to write a monadic variadic function, with parameters using the monadic context

I'm trying to make a variadic function with a monadic return type, whose parameters also require the monadic context. (I'm not sure how to describe that second point: e.g. printf can return IO () but it's different in that its parameters are treated the same whether it ends up being IO () or String.)
Basically, I've got a data constructor that takes, say, two Char parameters. I want to provide two pointer style ID Char arguments instead, which can be automagically decoded from an enclosing State monad via a type class instance. So, instead of doing get >>= \s -> foo1adic (Constructor (idGet s id1) (idGet s id2)), I want to do fooVariadic Constructor id1 id2.
What follows is what I've got so far, Literate Haskell style in case somebody wants to copy it and mess with it.
First, the basic environment:
> {-# LANGUAGE FlexibleContexts #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> import Control.Monad.Trans.State
> data Foo = Foo0
> | Foo1 Char
> | Foo2 Bool Char
> | Foo3 Char Bool Char
> deriving Show
> type Env = (String,[Bool])
> newtype ID a = ID {unID :: Int}
> deriving Show
> class InEnv a where envGet :: Env -> ID a -> a
> instance InEnv Char where envGet (s,_) i = s !! unID i
> instance InEnv Bool where envGet (_,b) i = b !! unID i
Some test data for convenience:
> cid :: ID Char
> cid = ID 1
> bid :: ID Bool
> bid = ID 2
> env :: Env
> env = ("xy", map (==1) [0,0,1])
I've got this non-monadic version, which simply takes the environment as the first parameter. This works fine but it's not quite what I'm after. Examples:
$ mkFoo env Foo0 :: Foo
Foo0
$ mkFoo env Foo3 cid bid cid :: Foo
Foo3 'y' True 'y'
(I could use functional dependencies or type families to get rid of the need for the :: Foo type annotations. For now I'm not fussed about it, since this isn't what I'm interested in anyway.)
> mkFoo :: VarC a b => Env -> a -> b
> mkFoo = variadic
>
> class VarC r1 r2 where
> variadic :: Env -> r1 -> r2
>
> -- Take the partially applied constructor, turn it into one that takes an ID
> -- by using the given state.
> instance (InEnv a, VarC r1 r2) => VarC (a -> r1) (ID a -> r2) where
> variadic e f = \aid -> variadic e (f (envGet e aid))
>
> instance VarC Foo Foo where
> variadic _ = id
Now, I want a variadic function that runs in the following monad.
> type MyState = State Env
And basically, I have no idea how I should proceed. I've tried expressing the type class in different ways (variadicM :: r1 -> r2 and variadicM :: r1 -> MyState r2) but I haven't succeeded in writing the instances. I've also tried adapting the non-monadic solution above so that I somehow "end up" with an Env -> Foo which I could then easily turn into a MyState Foo, but no luck there either.
What follows is my best attempt thus far.
> mkFooM :: VarMC r1 r2 => r1 -> r2
> mkFooM = variadicM
>
> class VarMC r1 r2 where
> variadicM :: r1 -> r2
>
> -- I don't like this instance because it requires doing a "get" at each
> -- stage. I'd like to do it only once, at the start of the whole computation
> -- chain (ideally in mkFooM), but I don't know how to tie it all together.
> instance (InEnv a, VarMC r1 r2) => VarMC (a -> r1) (ID a -> MyState r2) where
> variadicM f = \aid -> get >>= \e -> return$ variadicM (f (envGet e aid))
>
> instance VarMC Foo Foo where
> variadicM = id
>
> instance VarMC Foo (MyState Foo) where
> variadicM = return
It works for Foo0 and Foo1, but not beyond that:
$ flip evalState env (variadicM Foo1 cid :: MyState Foo)
Foo1 'y'
$ flip evalState env (variadicM Foo2 cid bid :: MyState Foo)
No instance for (VarMC (Bool -> Char -> Foo)
(ID Bool -> ID Char -> MyState Foo))
(Here I would like to get rid of the need for the annotation, but the fact that this formulation needs two instances for Foo makes that problematic.)
I understand the complaint: I only have an instance that goes from Bool ->
Char -> Foo to ID Bool -> MyState (ID Char -> Foo). But I can't make the
instance it wants because I need MyState in there somewhere so that I can
turn the ID Bool into a Bool.
I don't know if I'm completely off track or what. I know that I could solve my basic issue (I don't want to pollute my code with the idGet s equivalents all over the place) in different ways, such as creating liftA/liftM-style functions for different numbers of ID parameters, with types like (a -> b -> ... -> z -> ret) -> ID a -> ID b -> ... -> ID z -> MyState ret, but I've spent too much time thinking about this. :-) I want to know what this variadic solution should look like.
WARNING
Preferably don't use variadic functions for this type of work. You only have a finite number of constructors, so smart constructors don't seem to be a big deal. The ~10-20 lines you would need are a lot simpler and more maintainable than a variadic solution. Also an applicative solution is much less work.
WARNING
The monad/applicative in combination with variadic functions is the problem. The 'problem' is the argument addition step used for the variadic class. The basic class would look like
class Variadic f where
func :: f
-- possibly with extra stuff
where you make it variadic by having instances of the form
instance Variadic BaseType where ...
instance Variadic f => Variadic (arg -> f) where ...
Which would break when you would start to use monads. Adding the monad in the class definition would prevent argument expansion (you would get :: M (arg -> f), for some monad M). Adding it to the base case would prevent using the monad in the expansion, as it's not possible (as far as I know) to add the monadic constraint to the expansion instance. For a hint to a complex solution see the P.S..
The solution direction of using a function which results in (Env -> Foo) is more promising. The following code still requires a :: Foo type constraint and uses a simplified version of the Env/ID for brevity.
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}
module Test where
data Env = Env
data ID a = ID
data Foo
= Foo0
| Foo1 Char
| Foo2 Char Bool
| Foo3 Char Bool Char
deriving (Eq, Ord, Show)
class InEnv a where
resolve :: Env -> ID a -> a
instance InEnv Char where
resolve _ _ = 'a'
instance InEnv Bool where
resolve _ _ = True
The Type families extension is used to make the matching stricter/better. Now the variadic function class.
class MApp f r where
app :: Env -> f -> r
instance MApp Foo Foo where
app _ = id
instance (MApp r' r, InEnv a, a ~ b) => MApp (a -> r') (ID b -> r) where
app env f i = app env . f $ resolve env i
-- using a ~ b makes this instance to match more easily and
-- then forces a and b to be the same. This prevents ambiguous
-- ID instances when not specifying there type. When using type
-- signatures on all the ID's you can use
-- (MApp r' r, InEnv a) => MApp (a -> r') (ID a -> r)
-- as constraint.
The environment Env is explicitly passed, in essence the Reader monad is unpacked preventing the problems between monads and variadic functions (for the State monad the resolve function should return a new environment). Testing with app Env Foo1 ID :: Foo results in the expected Foo1 'a'.
P.S.
You can get monadic variadic functions to work (to some extent) but it requires bending your functions (and mind) in some very strange ways. The way I've got such things to work is to 'fold' all the variadic arguments into a heterogeneous list. The unwrapping can then be done monadic-ally. Though I've done some things like that, I strongly discourage you from using such things in actual (used) code as it quickly gets incomprehensible and unmaintainable (not to speak of the type errors you would get).

Resources