[Haskell-beginners] Trouble in (Fast)CGI land: matching `CGIT IO a0' with actual type `IO ()'

David McBride toad3k at gmail.com
Mon Mar 11 04:31:06 CET 2013


Let me put it plainly.  I'm not going to explain the theory, just cold
hard practicality of how to do what you want to do when you see this
in the wild, which you will if you haven't already.

Let's call this a pattern in haskell.  It is the monad transformer
pattern, which you'll see many (possibly even most) libraries use at
one time or another once they get past a certain amount of complexity.
 When you don't understand it, you feel like you can't quite do
anything in haskell, at least not without copy paste or lots of random
fiddling. But then once you know it, suddenly most of the libraries in
the language open up to you.  At least that is how it was for me.

Whenever you see a library that has a runBlah function which will have
a type:  Blah a -> IO b.  Examples:

shelly :: MonadIO m => Sh a -> m a (from the shelly library)

runStateT :: StateT s m a -> s -> m (a, s)  (from control.monad.state)

runInputT :: MonadException m => Settings m -> InputT m a -> m a (from
haskeline)

runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a (from
the resourceT package)

atomically :: STM a -> IO a (from base, from the shared transactional
memory related functions)

runParserT :: Stream s m t => ParsecT s u m a -> u -> SourceName -> s
-> m (Either ParseError a) (from parsec)

runFastCGI :: CGI CGIResult -> IO () (from the fastcgi library)

So as you can see they are different, but they all have some
similarities in that they all return either IO a, or possibly m a
where m has some class restrictions on it.  IO will almost always meet
those restrictions if you try it.  Sometimes they have special
arguments to get their environments set up so that they have the info
they need to work.  Sometimes they don't.  What they all have in
common is that they all take an argument that sort of lives in a
specific type (InputT, ResourceT, ParsecT, Sh, STM, StateT, etc.).
Sometimes there are several alternatives with slightly different
functionality.

If you find a function that returns one of those types, then it was
meant to be run as an argument to a function like one of these.
Sometimes the types are simplified with type aliases so you don't
always recognize them off the bat.  Parser a aliases to Parsec String
() a which is an alias for ParsecT String () Identity a.  In your
original message it was the case that CGI CGIResult is an alias for
CGIT IO CGIResult, so the base monad was in that case CGIT, and not
CGI.

So you've figured this out, now you can run a procedure composed of
functions which return CGI a.  Suddenly you realize in the middle of
the procedure you need to run an IO function.  Perhaps you need to get
some info from a file.  Well each of these monads uses the transformer
library.  If you go onto hackage and you look up say, ParsecT for
example, you will see a whole lot of instances like these for each of
them.

MonadError e m => MonadError e (ParsecT s u m)
MonadReader r m => MonadReader r (ParsecT s u m)
MonadState s m => MonadState s (ParsecT s' u m)
MonadTrans (ParsecT s u)
Monad (ParsecT s u m)
Functor (ParsecT s u m)
MonadPlus (ParsecT s u m)
Applicative (ParsecT s u m)
Alternative (ParsecT s u m)
MonadIO m => MonadIO (ParsecT s u m)
MonadCont m => MonadCont (ParsecT s u m)

These instances all represent different tricks that can be performed
while stuck in the ParsecT monad.  The one that concerns us right now
is that instance for MonadIO.  Any type that is an instance of MonadIO
has the ability to use the liftIO function, which is defined in the
MonadIO class.  All this lets you do is call any IO function in it.
Sometimes the instance is a little wonky and you might not recognize
it right off the bat, for example:

(Monad (CGIT m), MonadIO m) => MonadIO (CGIT m)

So, is CGIT an instance of MonadIO or not?  Well it is if CGIT m is a
Monad and the m, whatever it is, is an instance MonadIO.  If you look
at IO, IO happens to be an instance of MonadIO, so therefore you can
use liftIO in there whenever you please.  Now lets look at the
instances for STM:

Monad STM
Functor STM
Typeable1 STM
MonadPlus STM
Applicative STM
Alternative STM

Huh there's no MonadIO instance here.  How am I supposed to read my
file?  Well the answer is that STM is meant for atomic actions and the
only way it can guarantee that no one tried to do anything funny while
it was in the STM monad is to restrict it so that you cannot do IO in
the middle of it.  There is no real way to subvert it, since you don't
have access to the internals of STM, you could never write a MonadIO
instance for it.  The designer intended it to be this way.  That tells
you quite a bit about what that library was intended for.

So now notice all those other instances.  What do they do?  Well they
do lots of useful things the library writer thought you might like to
be able to do.

Applicative lets you use applicative style programming within the
monad.  You can see tons of examples of that in Parsec, just google
it.

Alternative allows you to use the alternative operator when you are
within that monad, which I find super useful and I wish people used it
more.  So you can try to do one thing and if it fails, try another (x
<- (tryA <|> tryB)).  It can be used to greatly simplify code,
especially in parsers.

Functor allows you to fmap its return result to another type without
exiting the monad.  (string <- fmap show $ (char 'a' :: Parser Char)
:: Parser String) from parsec for example.  This is a really common
one and nearly all such types will have a Functor instance.

MonadState would allow you to get and set a variable in the monad's
environment.  Sometimes that state is set by you in the run function
(which in fact it is for both StateT and ParsecT).  Sometimes it is
the internal state of the library.  If you can supply it you can use
it to carry some arbitrary state along the program for you, and access
and update it whenever you need to, and even return it at the end.

So when you see a mysterious monad somewhere in a library, give it a
look on hackage.  You may find that it has some sensible functionality
for you to make use of.  You may also get a sense of how the library
creator expects you to use his library.

On Sun, Mar 10, 2013 at 7:21 PM, emacstheviking <objitsu at gmail.com> wrote:
>
> David,
>
> At times like this I think am not even fit to code PHP for my day job.
> I am going to have to read that very carefully when I wake up tomorrow.
>
> Thanks.
>
>
>
> On 10 March 2013 22:59, David McBride <toad3k at gmail.com> wrote:
>>
>> Your ipCamExec is IO (), but you are running it in the CGI a monad which is a type alias for CGIT IO a.  CGIT is an instance of MonadIO, so try liftIO ipCamExec.  liftIO has a type MonadIO m => IO a -> m a, which means that if you replace m with CGIT IO, you would get IO a -> CGIT IO a, which is exactly what you need.
>>
>> On Sun, Mar 10, 2013 at 6:40 PM, emacstheviking <objitsu at gmail.com> wrote:
>>>
>>> I am writing a stop-motion capture application using AngularJS and it's going OK. I was inspired to do so after installing "IPCamera" on my phone and Sony tablet. A typical IPCamera session lives on an internal address like this, this example will turn on the LED on the camera:
>>>
>>>    http://192.168.0.5:8080/enabletorch
>>>
>>> Just because I can (or so I thought), I decided to write a tiny little FastCGI application in Haskell to act as a proxy using the PATH_INFO variable. This means that in to my Javascript code I have this code in a service file:
>>>
>>> angular.module('stomoServices', ['ngResource']).
>>>     factory(
>>> 'IPCamera',
>>> function($resource, urlIPCameraAPI) {
>>>    return $resource(
>>> urlIPCameraAPI,
>>> {}, {
>>>    ledOn:    { method: 'GET', params: {featureReq: 'enabletorch' }},
>>>    ledOff:   { method: 'GET', params: {featureReq: 'disabletorch' }},
>>>    focusOn:  { method: 'GET', params: {featureReq: 'focus' }},
>>>    focusOff: { method: 'GET', params: {featureReq: 'nofocus'}}
>>> });
>>> });
>>>
>>> and I then issue commands like "IPCamera.ledOn()" etc. All very nice except that it doesn't work yet because I can't get the worlds seemingly simplest CGI application to compile yet! Here is the code that I have, it could be "cleared up" but this is what I have so far:
>>>
>>> main :: IO ()
>>> main = runFastCGI . handleErrors $ do
>>>   command <- getVar "PATH_INFO"
>>>   case command of
>>>     Nothing  ->
>>>       outputError 400 "Missing IPCamera instruction (PATH_INFO)" []
>>>     Just cmd ->
>>>       ipCamExec (tail cmd) >> output "OK" -- tail drops the "/"
>>>       where
>>>         ipCamExec :: String -> IO ()
>>>         ipCamExec url = do
>>>           simpleHTTP (getRequest url) -- don't want or need response.
>>>           return () -- to match the return type or so I thought.
>>>
>>> and the error message I cannot seem to understand as it fills me with monadic fear which I can't get out of:
>>>
>>> ipcamera.hs:16:7:
>>>     Couldn't match expected type `CGIT IO a0' with actual type `IO ()'
>>>     In the return type of a call of `ipCamExec'
>>>     In the first argument of `(>>)', namely `ipCamExec (tail cmd)'
>>>     In the expression: ipCamExec (tail cmd) >> output "OK"
>>>
>>> Please could some kind souls explain to me in simple terms just what is going on and why I am close to tears right now? I have read the definitions of CGIResult and CGI and they leave me cold. I am trying to understand monads more but at times like this I once again realise what a complete rank beginner I am!
>>>
>>> Thanks.
>>> Sean.
>>>
>>>
>>> _______________________________________________
>>> Beginners mailing list
>>> Beginners at haskell.org
>>> http://www.haskell.org/mailman/listinfo/beginners
>>>
>>
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



More information about the Beginners mailing list