Exporting a polymorphic MonadState function for a particular state data type - haskell

What I'm trying to do is (in a module I'm writing) export a function that works on a particular type in a state monad (in the example below, that type would be Foo). However I would like the user to be able to use the function in whatever MonadState type they wish: State.Lazy, State.Strict, StateT, etc. So it needs to be polymorphic in its outer state monad.
Here is an example of what I'd like to do:
EDITED with a better question:
import Control.Monad.State
data Foo a = Foo { cnt :: Int, val :: a }
--test :: State (Foo a) a -- THIS WORKS
--test :: StateT (Foo a) Maybe a -- ...SO DOES THIS
-- ... BUT INCLUDING THE FOLLOWING SIGNATURE GIVES AN ERROR:
test :: MonadState (Foo a) m => m a
test = modify (\(Foo i a)-> Foo (i+1) a) >> gets val
GHC complains that FlexibleInstances extension is required to define the type above. Is using that extension the correct way to define my function or is there a better way?
Thanks

Can't you just use the MonadState typeclass?
{-# LANGUAGE FlexibleContexts #-}
import Control.Monad.State
data Foo a = Foo { cnt :: Int, val :: a }
test :: MonadState (Foo a) m => m a
test = modify (\(Foo i a)-> Foo (i+1) a) >> gets val
It loads fine in GHCi.
EDIT: This is with MTL-2.0 and GHCi-7.0.1

Related

newtype with gadt-like constraint

I understand why you can't do this:
{-# LANGUAGE GADTs #-}
newtype NG a where MkNG :: Eq a => a -> NG a
-- 'A newtype constructor cannot have a context in its type', says GHC
That's because the 'data' constructor MkNG is not really a constructor. "The constructor N in an expression coerces a value from type t to type ..." says the language report, Section 4.2.3 "Unlike algebraic datatypes, the newtype constructor N is unlifted, ..."
If it were to be able to support a constraint, it would need an argument position for the constraint's dictionary.
Now I've got your attention I'm going to ask about that deprecated feature, for which you often see (very old) StackOverflow answers saying to use GADTs instead:
{-# LANGUAGE DatatypeContexts #-} -- deprecated ~2010
newtype Eq a => NC a = MkNC a -- inferred MkNC :: Eq a => a -> NC a
-- nc = MkNC (id :: Int -> Int) -- rejected no Eq instance
quux (MkNC _) = () -- inferred quux :: Eq a => NC a -> ()
quuz (x :: NC a) = () -- inferred quuz :: NC a -> ()
(That type for quuz is one of the annoyances with DatatypeContexts: because the constructor doesn't appear in the pattern match, type inference can't 'see' the constraint.)
So this works (or doesn't depending on your point of view) just as well (or badly) as DatatypeContexts on data types.
My question is: how? MkNC again just coerces a value/is unlifted. Does it use dictionary-passing to apply the constraint? Where does the dictionary slot in, given that the coercion is purely a compile-time effect?

Checking constraints at runtime

I'm trying to define a function that detects whether the type of an input satisfies a given constraint:
satisfies :: (c a => a -> b) -> a -> Maybe b
-- or the more general
claim :: (c => a) -> Maybe a
So the desired behaviour would be:
>>> :t satisfies #Show show
satisfies #Show show :: a -> Maybe String
>>> satisfies #Show show (0 :: Int)
Just "0"
>>> satisfies #Show show (id :: Int -> Int)
Nothing
The goal is to make it easy to define fully polymorphic functions that take
advantage of specializations when possible:
showAny :: a -> String
showAny (satisfies #Show show -> Just str) = str
showAny (satisfies #Typeable showType -> Just str) = "_ :: " ++ str
showAny _ = "_"
As the easiest thing I could try, my first attempt tried using -fdefer-to-runtime
{-# OPTIONS_GHC -fdefer-type-errors -Wno-deferred-type-errors #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RankNTypes #-}
module Claim where
import System.IO.Unsafe (unsafePerformIO)
import System.IO.Error (catchIOError)
satisfies :: (c a => a -> b) -> a -> Maybe b
satisfies f a = unsafePerformIO $
(return . Just $! f a) `catchIOError` \_ -> return Nothing
This failed because -fdefer-type-errors doesn't defer the checking to
runtime, or allow further checking to be done in the context which it is
actually used (as I had hoped), but instead at compile time replaces found
type errors with the equivalent of error "MESSAGE".
Now I'm out of ideas. Is implementing satisfies even possible?
You can't dispatch on instance availability at runtime. Remember, a constraint is translated by the compiler into a type class dictionary - a record of functions that is passed around explicitly and accessed explicitly at runtime. The "fat arrow" => is represented at runtime by a "thin arrow" ->, so the elaborator needs to know at compile time which dictionary to pass around.
That is, the following crude example:
class Show a where
show :: a -> String
instance Show String where
show = id
showTwice :: Show a => a -> String
showTwice x = show x ++ show x
main = putStrLn $ showTwice "foo"
generates Core code which looks approximately like:
data Show_ a = Show_ { show :: a -> String }
showString_ :: Show_ String
showString_ = Show_ { show = id }
showTwice :: Show_ a -> a -> String
showTwice show_ x = show show_ x ++ show show_ x
main = putStrLn $ showTwice showString_ "foo"
When generating code for main, the compiler needs to know where to find showString_.
You can imagine a system wherein you can look up a type class dictionary at runtime with some sort of introspection mechanism, but this would produce weird behaviour from a language design perspective. The problem is orphan instances. If I write a function which attempts to look up a given instance in module A, and define such an instance in an unrelated module B, then the behaviour of that function when called from some client module C depends on whether B was imported by some other part of the program. Pretty strange!
A more usual way of doing "fully polymorphic functions that take advantage of specializations when possible" would be to put the function in question into a type class itself and give it a default implementation (perhaps with a default signature if the default implementation depends on some superclass). Your showAny would then look like this:
{-# LANGUAGE DefaultSignatures #-}
import Data.Typeable
class ShowAny a where
showAny :: a -> String
default showAny :: Typeable a => a -> String
showAny x = "_ :: " ++ show (typeOf x)
You'd need to implement ShowAny for all of the types with which you want to use showAny, but that's usually a single line of code,
instance (Typeable a, Typeable b) => ShowAny (a -> b)
and you can specialise an implementation for a given type just by overriding showAny.
instance ShowAny String where
showAny = id
You see this approach quite frequently in libraries which do generic programming. aeson, for example, can use GHC.Generics to serialise a given type to and from JSON (all you have to do is derive Generic and write two lines instance ToJSON MyType; instance FromJSON MyType), but you can also write your own instances of ToJSON and FromJSON if the generic code isn't fast enough or you need to customise the output.
An alternate workaround to the accepted answer is to pass the dictionaries around manually.
That is, given:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
module Claim where
data Proof c where QED :: c => Proof c
type Claim c = Maybe (Proof c)
type c ? a = Maybe (Proof (c a))
One can write:
showAny :: (Show? a, Typeable? a) -> a -> String
showAny (Just QED, _) a = show a
showAny (_, Just QED) a = "_ :: " ++ showType a
showAny _ _ = "_"
Which works accepably well:
>>> showAny (Nothing, Just QED) (id :: Int -> Int)
"_ :: Int -> Int"
>>> showAny (Just QED, Just QED) (0 :: Int)
"0"
>>> showAny (Nothing, Nothing) undefined
"_"

What is the difference between `DeriveAnyClass` and an empty instance?

Using the cassava package, the following compiles:
{-# LANGUAGE DeriveGeneric #-}
import Data.Csv
import GHC.Generics
data Foo = Foo { foo :: Int } deriving (Generic)
instance ToNamedRecord Foo
However, the following does not:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
import Data.Csv
import GHC.Generics
data Foo = Foo { foo :: Int } deriving (Generic, ToNamedRecord)
The compiler reports:
test.hs:7:50:
No instance for (ToNamedRecord Int)
arising from the first field of ‘Foo’ (type ‘Int’)
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (ToNamedRecord Foo)
This leaves me with two questions: Why isn't the second version identical to the first? And why is the compiler hoping to find an instance for ToNamedRecord Int?
NB: As pointed out by David in the comments, GHC has been updated since I wrote this. The code as written in the question compiles and works correctly. So just imagine everything below is written in the past tense.
The GHC docs say:
The instance context will be generated according to the same rules
used when deriving Eq (if the kind of the type is *), or the rules for
Functor (if the kind of the type is (* -> *)). For example
instance C a => C (a,b) where ...
data T a b = MkT a (a,b) deriving( C )
The deriving clause will
generate
instance C a => C (T a b) where {}
The constraints C a and C (a,b) are generated from the data constructor arguments, but the
latter simplifies to C a.
So, according to the Eq rules, your deriving clause generates...
instance ToNamedRecord Int => ToNamedRecord Foo where
... which is not the same as...
instance ToNamedRecord Foo where
... in that the former is only valid if there's an instance ToNamedRecord Int in scope (which is appears there isn't in your case).
But I find the spec to be somewhat ambiguous. Should the example really generate that code, or should it generate instance (C a, C (a, b)) => instance C (T a b) and let the solver discharge the second constraint? It appears, in your example, that it's generating such constraints even for fields with fully-concrete types.
I hesitate to call this a bug, because it's how Eq works, but given that DeriveAnyClass is intended to make it quicker to write empty instances it does seem unintuitive.

Combining multiple states in StateT

I am writing a program that runs as a daemon.
To create the daemon, the user supplies a set of
implementations for each of the required classes (one of them is a database)
All of these classes have functions have
type signatures of the form StateT s IO a,
but s is different for each class.
Suppose each of the classes follows this pattern:
import Control.Monad (liftM)
import Control.Monad.State (StateT(..), get)
class Hammer h where
driveNail :: StateT h IO ()
data ClawHammer = MkClawHammer Int -- the real implementation is more complex
instance Hammer ClawHammer where
driveNail = return () -- the real implementation is more complex
-- Plus additional classes for wrenches, screwdrivers, etc.
Now I can define a record that represents the implementation chosen by
the user for each "slot".
data MultiTool h = MultiTool {
hammer :: h
-- Plus additional fields for wrenches, screwdrivers, etc.
}
And the daemon does most of its work in the StateT (MultiTool h ...) IO ()
monad.
Now, since the multitool contains a hammer, I can use it in any situation
where a hammer is needed. In other words, the MultiTool type
can implement any of the classes it contains, if I write code like this:
stateMap :: Monad m => (s -> t) -> (t -> s) -> StateT s m a -> StateT t m a
stateMap f g (StateT h) = StateT $ liftM (fmap f) . h . g
withHammer :: StateT h IO () -> StateT (MultiTool h) IO ()
withHammer runProgram = do
t <- get
stateMap (\h -> t {hammer=h}) hammer runProgram
instance Hammer h => Hammer (MultiTool h) where
driveNail = withHammer driveNail
But the implementations of withHammer, withWrench, withScrewdriver, etc.
are basically identical. It would be nice to be able to write something
like this...
--withMember accessor runProgram = do
-- u <- get
-- stateMap (\h -> u {accessor=h}) accessor runProgram
-- instance Hammer h => Hammer (MultiTool h) where
-- driveNail = withMember hammer driveNail
But of course that won't compile.
I suspect my solution is too object-oriented.
Is there a better way?
Monad transformers, maybe?
Thank you in advance for any suggestions.
If you want to go with a large global state like in your case, then what you want to use is lenses, as suggested by Ben. I too recommend Edward Kmett's lens library. However, there is another, perhaps nicer way.
Servers have the property that the program runs continuously and performs the same operation over a state space. The trouble starts when you want to modularize your server, in which case you want more than just some global state. You want modules to have their own state.
Let's think of a module as something that transforms a Request to a Response:
Module :: (Request -> m Response) -> Module m
Now if it has some state, then this state becomes noticable in that the module might give a different answer the next time. There are a number of ways to do this, for example the following:
Module :: s -> ((Request, s) -> m (Response s)) -> Module m
But a much nicer and equivalent way to express this is the following constructor (we will build a type around it soon):
Module :: (Request -> m (Response, Module m)) -> Module m
This module maps a request to a response, but along the way also returns a new version of itself. Let's go further and make requests and responses polymorphic:
Module :: (a -> m (b, Module m a b)) -> Module m a b
Now if the output type of a module matches another module's input type, then you can compose them like regular functions. This composition is associative and has a polymorphic identity. This sounds a lot like a category, and in fact it is! It is a category, an applicative functor and an arrow.
newtype Module m a b =
Module (a -> m (b, Module m a b))
instance (Monad m) => Applicative (Module m a)
instance (Monad m) => Arrow (Module m)
instance (Monad m) => Category (Module m)
instance (Monad m) => Functor (Module m a)
We can now compose two modules that have their own individual local state without even knowing about it! But that's not sufficient. We want more. How about modules that can be switched among? Let's extend our little module system such that modules can actually choose not to give an answer:
newtype Module m a b =
Module (a -> m (Maybe b, Module m a b))
This allows another form of composition that is orthogonal to (.): Now our type is also a family of Alternative functors:
instance (Monad m) => Alternative (Module m a)
Now a module can choose whether to respond to a request, and if not, the next module will be tried. Simple. You have just reinvented the wire category. =)
Of course you don't need to reinvent this. The Netwire library implements this design pattern and comes with a large library of predefined "modules" (called wires). See the Control.Wire module for a tutorial.
Here's a concrete example of how to use lens like everybody else is talking about. In the following code example, Type1 is the local state (i.e. your hammer), and Type2 is the global state (i.e. your multitool). lens provides the zoom function which lets you run a localized state computation that zooms in on any field defined by a lens:
import Control.Lens
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.State
data Type1 = Type1 {
_field1 :: Int ,
_field2 :: Double}
field1 :: SimpleLens Type1 Int
field1 = lens _field1 (\x a -> x { _field1 = a})
field2 :: SimpleLens Type1 Double
field2 = lens _field2 (\x a -> x { _field2 = a})
data Type2 = Type2 {
_type1 :: Type1 ,
_field3 :: String}
type1 :: SimpleLens Type2 Type1
type1 = lens _type1 (\x a -> x { _type1 = a})
field3 :: SimpleLens Type2 String
field3 = lens _field3 (\x a -> x { _field3 = a})
localCode :: StateT Type1 IO ()
localCode = do
field1 += 3
field2 .= 5.0
lift $ putStrLn "Done!"
globalCode :: StateT Type2 IO ()
globalCode = do
f1 <- zoom type1 $ do
localCode
use field1
field3 %= (++ show f1)
f3 <- use field3
lift $ putStrLn f3
main = runStateT globalCode (Type2 (Type1 9 4.0) "Hello: ")
zoom is not limited to immediate sub-fields of a type. Since lenses are composable, you can zoom as deep as you want in a single operation just by doing something like:
zoom (field1a . field2c . field3b . field4j) $ do ...
This sounds very much like an application of lenses.
Lenses are a specification of a sub-field of some data. The idea is you have some value toolLens and functions view and set so that view toolLens :: MultiTool h -> h fetches the tool and set toolLens :: MultiTool h -> h -> MultiTool h replaces it with a new value. Then you can easily define your withMember as a function just accepting a lens.
Lens technology has advanced a great deal recently, and they are now incredibly capable. The most powerful library around at the time of writing is Edward Kmett's lens library, which is a bit much to swallow, but pretty simple once you find the features you want. You can also search for more questions about lenses here on SO, e.g. Functional lenses which links to lenses, fclabels, data-accessor - which library for structure access and mutation is better, or the lenses tag.
I created a lensed extensible record library called data-diverse-lens which allows combining multiple ReaderT (or StateT) like this gist:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
module Main where
import Control.Lens
import Control.Monad.Reader
import Control.Monad.State
import Data.Diverse.Lens
import Data.Semigroup
foo :: (MonadReader r m, HasItem' Int r, HasItem' String r) => m (Int, String)
foo = do
i <- view (item' #Int) -- explicitly specify type
s <- view item' -- type can also be inferred
pure (i + 10, s <> "bar")
bar :: (MonadState s m, HasItem' Int s, HasItem' String s) => m ()
bar = do
(item' #Int) %= (+10) -- explicitly specify type
item' %= (<> "bar") -- type can also be inferred
pure ()
main :: IO ()
main = do
-- example of running ReaderT with multiple items
(i, s) <- runReaderT foo ((2 :: Int) ./ "foo" ./ nil)
putStrLn $ show i <> s -- prints out "12foobar"
-- example of running StateT with multiple items
is <- execStateT bar ((2 :: Int) ./ "foo" ./ nil)
putStrLn $ show (view (item #Int) is) <> (view (item #String) is) -- prints out "12foobar"
Data.Has is a simpler library that does the same with tuples. Example from the library front page:
{-# LANGUAGE FlexibleContexts #-}
-- in some library code
...
logInAnyReaderHasLogger :: (Has Logger r, MonadReader r m) => LogString -> m ()
logInAnyReaderHasLogger s = asks getter >>= logWithLogger s
queryInAnyReaderHasSQL :: (Has SqlBackEnd r, MonadReader r m) => Query -> m a
queryInAnyReaderHasSQL q = asks getter >>= queryWithSQL q
...
-- now you want to use these effects together
...
logger <- initLogger ...
sql <- initSqlBackEnd ...
(`runReader` (logger, sql)) $ do
...
logInAnyReaderHasLogger ...
...
x <- queryInAnyReaderHasSQL ...
...

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