
Hi, I'm trying to work out how to handle a choice at runtime which determines what instance of a State monad should be used. The choice will dictate the internal state of the monad so different implementations are needed for each. I've concocted a very simple example to illustrate this (below) - but it doesn't compile because ghc complains that my type is ambiguous arising from my use of 'fromSeq'. I can kind-of see what the compiler is complaining about, I'm guessing because it is the internals of my type which dictate which state Monad to use and it can't know that? Thinking about it I tried making SeqType an instance of Sequence class, but had no luck here. I understand that haskell is static at compile time, so I'm looking for something like a template solution in C++ (rather than a virtual function style implementation). I see there are libraries out their which do this, but I was wondering in my simple example if there was a way of doing this without writing a load of boilerplate code in main (this would get ugly very quickly if you had loads of choices). If this is impossible does anyone have an example / advice of implementing simple template style code in Haskell? Any help or suggestions would be really appreciated. Many Thanks, Phil. Thus just implements a state Monad which counts up from 1 to 10, using either an Int or a Double depending on user choice. It's pointless of course, but illustrates my point. {-# LANGUAGE TypeSynonymInstances #-} import Control.Monad.State.Strict data SeqType = SeqDouble Double | SeqInt Int class SequenceClass a where nextSeq :: State a Int fromSeq :: SeqType -> a instance SequenceClass Int where nextSeq = State $ \s -> (s,s+1) fromSeq (SeqInt i) = i fromSeq _ = 0 instance SequenceClass Double where nextSeq = State $ \s -> (truncate s,s+1.0) fromSeq (SeqDouble d) = d fromSeq _ = 0.0 chooser :: String -> SeqType chooser inStr | inStr == "Double" = SeqDouble 1.0 | inStr == "Int" = SeqInt 1 | otherwise = SeqInt 1 main :: IO() main = do userInput <- getLine let result = evalState (do replicateM 10 nextSeq) $ fromSeq $ chooser userInput print result