Working with the code For "Typing Haskell In Haskell"

Hi all, I'm working with the code that accompanies this paper (http://web.cecs.pdx.edu/~mpj/thih/) and I'm trying to use it but I can't figure out how to get started. I have the following code but it is not giving me the expected result: import TypingHaskellInHaskell mapt = "map" :>: Forall [Star, Star] ([] :=> ((TGen 0 `fn` TGen 1) `fn` TAp tList (TGen 0) `fn` TAp tList (TGen 1))) idt = "id" :>: Forall [Star] ([] :=> (TGen 0 `fn` TGen 0)) exprt = Ap (Const mapt) (Const idt) test = runTI $ tiExpr initialEnv [] exprt When I execute the test function above in ghci I get: ([],TVar (Tyvar "v3" Star)). I was expecting someting like below for the type part: TAp tList (TGen 0) `fn` TAp tList (TGen 0) What I want is the library to compute for me the type of "map id". What is the proper way to achieve this? Has anybody on the list worked with this code before? Thanks as lot, Patrick -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Patrick LeBoutillier
[...]
exprt = Ap (Const mapt) (Const idt)
test = runTI $ tiExpr initialEnv [] exprt
When I execute the test function above in ghci I get:
([],TVar (Tyvar "v3" Star)).
I was expecting someting like below for the type part:
TAp tList (TGen 0) `fn` TAp tList (TGen 0)
[...] Hi Patrick. The short answer is that you need to use a higher-level inference function than tiExpr. Here's the code I ended up with: t4 = (putStrLn . pretty . runTI) (tiImpls initialEnv [mapt, idt] [("map_id", [([], Var "map" `Ap` Var "id")])]) It gets the desired result: *PLB_thih> t4 ([], ["map_id" :>: Forall [Star] ([] :=> (TAp tList (TGen 0) `fn` TAp tList (TGen 0)))]) Var is for referring by name to type assumptions you already have. Const is intended for other things such as data constructors, so I avoided it in this case, even though Const mapt `Ap` Const idt also works. The tiImpls function performs the 'quantify' step, which adds the Forall and converts TVar to TGen, whereas tiExpr doesn't. I can't see offhand why tiExpr doesn't seem to work in isolation - but maybe that part of a Haskell typer wouldn't work in isolation either! Regards, Tom

Hello all, I want to have a web application using one 'index.html' file with ajax requests and a happstack web server which response to server requests. For that purpose I need to use some javascript libraries in my directory tree. I tried: main = simpleHTTP nullConf $ msum [ serveFile (asContentType "text/html") "index.html" , serveFile (asContentType "text/javascript") "javascript/js.js" ] The js.js - file will never be found in this way because after finding the index.html, the msum function stops (as described in the happstack crash course). If I change the order, I can see the source of js.js. I also tried leaving it. In every case, inside index.html a function defined in js.js cannot be called. (naturally, I sourced the file inside index.html) Is it possible to obtain the effect of beeing able to call a function in an external file without jmacro? I also tried: main = simpleHTTP nullConf $ msum [ dir "ok" $ ok "jeah!" , serveFile (asContentType "text/html") "index.html" Couldn't match expected type `[Char]' with actual type `Response' Expected type: ServerPartT IO [Char] Actual type: ServerPartT IO Response In the return type of a call of `serveFile' In the expression: serveFile (asContentType "text/html") "index.html" The webserver should take requests, and if there is none (no dir, personal convention), it should provide index.html. The error is because msum needs the same input types. Is it possible to transform one of these types to the other? It seems that my approach to the problem is not the right one, the one the authors thought about while programming. I wanted to have a clear seperation from logic (haskell) and interface (javascript). Is it right that using a running haskell webserver with the web application 'in it' is in general a faster solution than using for example apache with the fcgi module? Which approach would you prefer to realize such an ajax application? Greets Gary

Hi Gary,
A convention I use in my top-level handler is:
simpleHTTP nullConf $
msum
[ <dynamic content handler>
, serveDirectory DisableBrowsing [] "static"
, <404 handler>
]
where 'serveDirectory' is a function that ships with happstack-server
and serves up the contents of a directory which it is pointed at. I
then keep all of my static CSS and Javascript files in the static
directory.
The second argument to 'serveDirectory' is used to specify the
index-files to look for in a folder if the user browses to a static
folder, so here you could specify "index.html" to have
'serveDirectory' look for files named "index.html" and serve them up
when a top-level folder is requested.
Antoine
On Tue, Nov 1, 2011 at 9:48 AM, Gary Klindt
Hello all,
I want to have a web application using one 'index.html' file with ajax requests and a happstack web server which response to server requests. For that purpose I need to use some javascript libraries in my directory tree. I tried:
main = simpleHTTP nullConf $ msum [ serveFile (asContentType "text/html") "index.html" , serveFile (asContentType "text/javascript") "javascript/js.js" ]
The js.js - file will never be found in this way because after finding the index.html, the msum function stops (as described in the happstack crash course). If I change the order, I can see the source of js.js. I also tried leaving it. In every case, inside index.html a function defined in js.js cannot be called. (naturally, I sourced the file inside index.html)
Is it possible to obtain the effect of beeing able to call a function in an external file without jmacro?
I also tried:
main = simpleHTTP nullConf $ msum [ dir "ok" $ ok "jeah!" , serveFile (asContentType "text/html") "index.html"
Couldn't match expected type `[Char]' with actual type `Response' Expected type: ServerPartT IO [Char] Actual type: ServerPartT IO Response In the return type of a call of `serveFile' In the expression: serveFile (asContentType "text/html") "index.html"
The webserver should take requests, and if there is none (no dir, personal convention), it should provide index.html. The error is because msum needs the same input types. Is it possible to transform one of these types to the other?
It seems that my approach to the problem is not the right one, the one the authors thought about while programming. I wanted to have a clear seperation from logic (haskell) and interface (javascript). Is it right that using a running haskell webserver with the web application 'in it' is in general a faster solution than using for example apache with the fcgi module?
Which approach would you prefer to realize such an ajax application?
Greets Gary
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hey Antoine, thank you for answering. Your strategy is quite similar to the one I prefer. I misunderstood the behaviour of serveDirectory. The problem with external javascript files is solved. The other problem I had, was, that the argument 'msum' is a list, which has elements with the same type, so I needed a conversion from m [Char] to m Response. In Happstack.Server.Response there is a function, which actually does that: flatten: module Main where import Happstack.Server import Control.Monad main :: IO () main = simpleHTTP nullConf $ msum [ flatten $ dir "ok" $ ok "jeahh!" , serveDirectory DisableBrowsing ["index.html"] "static" ] Cheers On 11/01/2011 03:58 PM, Antoine Latter wrote:
Hi Gary,
A convention I use in my top-level handler is:
simpleHTTP nullConf $ msum [<dynamic content handler> , serveDirectory DisableBrowsing [] "static" ,<404 handler> ]
where 'serveDirectory' is a function that ships with happstack-server and serves up the contents of a directory which it is pointed at. I then keep all of my static CSS and Javascript files in the static directory.
The second argument to 'serveDirectory' is used to specify the index-files to look for in a folder if the user browses to a static folder, so here you could specify "index.html" to have 'serveDirectory' look for files named "index.html" and serve them up when a top-level folder is requested.
Antoine
On Tue, Nov 1, 2011 at 9:48 AM, Gary Klindt
wrote: Hello all,
I want to have a web application using one 'index.html' file with ajax requests and a happstack web server which response to server requests. For that purpose I need to use some javascript libraries in my directory tree. I tried:
main = simpleHTTP nullConf $ msum [ serveFile (asContentType "text/html") "index.html" , serveFile (asContentType "text/javascript") "javascript/js.js" ]
The js.js - file will never be found in this way because after finding the index.html, the msum function stops (as described in the happstack crash course). If I change the order, I can see the source of js.js. I also tried leaving it. In every case, inside index.html a function defined in js.js cannot be called. (naturally, I sourced the file inside index.html)
Is it possible to obtain the effect of beeing able to call a function in an external file without jmacro?
I also tried:
main = simpleHTTP nullConf $ msum [ dir "ok" $ ok "jeah!" , serveFile (asContentType "text/html") "index.html"
Couldn't match expected type `[Char]' with actual type `Response' Expected type: ServerPartT IO [Char] Actual type: ServerPartT IO Response In the return type of a call of `serveFile' In the expression: serveFile (asContentType "text/html") "index.html"
The webserver should take requests, and if there is none (no dir, personal convention), it should provide index.html. The error is because msum needs the same input types. Is it possible to transform one of these types to the other?
It seems that my approach to the problem is not the right one, the one the authors thought about while programming. I wanted to have a clear seperation from logic (haskell) and interface (javascript). Is it right that using a running haskell webserver with the web application 'in it' is in general a faster solution than using for example apache with the fcgi module?
Which approach would you prefer to realize such an ajax application?
Greets Gary
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Nov 1, 2011 at 9:48 AM, Gary Klindt
Hello all,
I want to have a web application using one 'index.html' file with ajax requests and a happstack web server which response to server requests. For that purpose I need to use some javascript libraries in my directory tree. I tried:
main = simpleHTTP nullConf $ msum [ serveFile (asContentType "text/html") "index.html" , serveFile (asContentType "text/javascript") "javascript/js.js" ]
As you discovered, serveDirectory is what you probably want. But, let's say you really want to use serveFile for some reason. The problem with your code is that each of those lines will response to *any* incoming request. You really want the first line to only respond to requests for /index.html and the second to only respond to requests for "/javascript/js.js". So you would need to rewrite you code like: simpleHTTP nullConf msum $ [ dir "index.html" $ serveFile (asContentType "text/html; charset=UTF-8") "index.html" , dir "javascript" $ dir "js.js" $ serveFile (asContentType "text/javascript") "javascript/js.js" ] That would allow you to request /index.html vs javascript/js.js. Now, obviously it is annoying to have to specify the names of the files twice. But that is because serveFile is not really intended to be used that way. serveFile is typically used when the name of the file in the request is different from the name of the file on the disk. For example, let's say we have an image gallery. When people upload images, they might have very common names like DSC_0123.jpg. So, we might get file collisions if we tried to use the original file name to store the file. Instead, we might rename the file to same unique name that we know won't have any collisions. But, we might have the url be something like, /image/theuniqueid/DSC_0123.jpg. That way when someone downloads the file, their original file name is still intact. That means we need some way to serve a file from the disk where the name of the file on the disk is not the same of the name of the file in the URL. For that scheme we would have something like: dir "image" $ path $ \uniqueid -> anyPath $ do locationOnDisk <- lookupDiskLocation uniqueId serveFile guessContentTypeM locationOnDisk where "lookDiskLocation" is some application specific function. - jeremy
participants (5)
-
Antoine Latter
-
Gary Klindt
-
Jeremy Shaw
-
Patrick LeBoutillier
-
Tom Pledger