Here you go:

module SimpleCgiServer
   where

import IO
import Char
import Network
import Control.Monad
import System.Process

listensocket = 2000

main = withSocketsDo $ do socket <- listenOn (PortNumber listensocket)
                          mapM_ (\_ -> handleconnection socket) (iterate (id) ())
                          sClose socket

handleconnection socket = do (handle,hostname,portnumber) <- accept socket
                             putStrLn (show(hostname) ++ " " ++ show(portnumber))
                             hSetBuffering handle LineBuffering
                             line <- hGetLine handle
                             let filename = drop( length("GET /") ) line
                             htmltoreturn <- runprocess filename
                             hPutStr handle htmltoreturn

runprocess filename = do (stdin,stdout,stderr,processhandle) <- runInteractiveCommand filename
                         waitForProcess processhandle
                         contents <- hGetContents stdout
                         return contents


You can change the portnumber by changing the value of the function "listensocket".

This expects you to send it something like "GET /test.bat".  It will run test.bat - or whatever filename you sent it - and send the results back down the socket.

It's obviously not at all secure, eg we're not filtering things like ".." from the input, so make sure to not publish the port to anywhere insecure (like the Internet).