{-# LANGUAGE
UnicodeSyntax
#-}
+import qualified Data.Collections as C
import MiseRafturai
import Network.HTTP.Lucu
main ∷ IO ()
-main = let config = defaultConfig { cnfServerPort = "9999" }
- resources = mkResTree [ ([], miseRafturai) ]
+main = let config = defaultConfig { cnfServerPort = "9999" }
+ tree ∷ ResourceTree
+ tree = C.fromList [ ([], nonGreedy miseRafturai) ]
in
do putStrLn "Access http://localhost:9999/ with your browser."
- runHttpd config resources []
+ runHttpd config $ resourceMap tree
{-# LANGUAGE
UnicodeSyntax
#-}
+import qualified Data.Collections as C
import Network.HTTP.Lucu
import SmallFile
main ∷ IO ()
-main = let config = defaultConfig { cnfServerPort = "9999" }
- resources = mkResTree [ ([], smallFile) ]
+main = let config = defaultConfig { cnfServerPort = "9999" }
+ tree ∷ ResourceTree
+ tree = C.fromList [ ([], nonGreedy smallFile) ]
in
do putStrLn "Access http://localhost:9999/ with your browser."
- runHttpd config resources []
-
\ No newline at end of file
+ runHttpd config $ resourceMap tree
#-}
import qualified Data.ByteString.Lazy.Char8 as Lazy
import Control.Applicative
+import qualified Data.Collections as C
import Control.Monad.Unicode
import Data.Maybe
import Data.Monoid.Unicode
import Network.HTTP.Lucu
main ∷ IO ()
-main = let config = defaultConfig { cnfServerPort = "9999" }
- resources = mkResTree [ ([], resMain) ]
+main = let config = defaultConfig { cnfServerPort = "9999" }
+ tree ∷ ResourceTree
+ tree = C.fromList [ ([], nonGreedy resMain) ]
in
do putStrLn "Access http://localhost:9999/ with your browser."
- runHttpd config resources []
+ runHttpd config $ resourceMap tree
-
-resMain ∷ ResourceDef
-resMain
- = emptyResource {
- resGet
- = Just $ do setContentType $ parseMIMEType "text/html"
- putChunks $ "<title>Multipart Form Test</title>\n"
- ⊕ "<form action=\"/\" method=\"post\" enctype=\"multipart/form-data\">\n"
- ⊕ " Upload some file:\n"
- ⊕ " <input type=\"text\" name=\"text\">\n"
- ⊕ " <input type=\"file\" name=\"file\">\n"
- ⊕ " <input type=\"submit\" value=\"Submit\">\n"
- ⊕ "</form>\n"
- , resPost
- = Just $ do form ← getForm Nothing
- let text = fromMaybe (∅) $ fdContent <$> lookup "text" form
- file = fromMaybe (∅) $ fdContent <$> lookup "file" form
- fileName = fdFileName =≪ lookup "file" form
- setContentType $ parseMIMEType "text/plain"
- putChunks $ "You entered \"" ⊕ text ⊕ "\".\n"
- putChunks $ "You uploaded a " ⊕ Lazy.pack (show $ Lazy.length file) ⊕ " bytes long file.\n"
- putChunks $ "The file name is " ⊕ Lazy.pack (show fileName) ⊕ ".\n"
- }
+resMain ∷ Resource
+resMain = C.fromList
+ [ ( GET
+ , do setContentType $ parseMIMEType "text/html"
+ putChunks $ "<title>Multipart Form Test</title>\n"
+ ⊕ "<form action=\"/\" method=\"post\" enctype=\"multipart/form-data\">\n"
+ ⊕ " Upload some file:\n"
+ ⊕ " <input type=\"text\" name=\"text\">\n"
+ ⊕ " <input type=\"file\" name=\"file\">\n"
+ ⊕ " <input type=\"submit\" value=\"Submit\">\n"
+ ⊕ "</form>\n"
+ )
+ , ( POST
+ , do form ← getForm Nothing
+ let text = fromMaybe (∅) $ fdContent <$> lookup "text" form
+ file = fromMaybe (∅) $ fdContent <$> lookup "file" form
+ fileName = fdFileName =≪ lookup "file" form
+ setContentType $ parseMIMEType "text/plain"
+ putChunks $ "You entered \"" ⊕ text ⊕ "\".\n"
+ putChunks $ "You uploaded a " ⊕ Lazy.pack (show $ Lazy.length file) ⊕ " bytes long file.\n"
+ putChunks $ "The file name is " ⊕ Lazy.pack (show fileName) ⊕ ".\n"
+ )
+ ]
, UnicodeSyntax
#-}
import Control.Applicative
-import "mtl" Control.Monad.Trans
+import Control.Monad.IO.Class
import Control.Monad.Unicode
import qualified Data.ByteString.Lazy.Char8 as Lazy
+import qualified Data.Collections as C
import Data.Time.Clock
import Network.HTTP.Lucu
import OpenSSL
SSL.contextSetCertificate ctx cert
SSL.contextSetDefaultCiphers ctx
- let config = defaultConfig {
- cnfServerPort = "9000"
- , cnfSSLConfig = Just SSLConfig {
- sslServerPort = "9001"
- , sslContext = ctx
- }
- }
- resources = mkResTree [ ([], helloWorld) ]
+ let config = defaultConfig {
+ cnfServerPort = "9000"
+ , cnfSSLConfig = Just SSLConfig {
+ sslServerPort = "9001"
+ , sslContext = ctx
+ }
+ }
+ tree ∷ ResourceTree
+ tree = C.fromList [ ([], nonGreedy helloWorld) ]
putStrLn "Access https://localhost:9001/ with your browser."
- runHttpd config resources []
+ runHttpd config $ resourceMap tree
-helloWorld ∷ ResourceDef
+helloWorld ∷ Resource
helloWorld
- = emptyResource {
- resGet
- = Just $ do setContentType [mimeType| text/plain |]
- putChunk "getRemoteCertificate = "
- cert ← do cert ← getRemoteCertificate
- case cert of
- Just c → liftIO $ Lazy.pack <$> printX509 c
- Nothing → return "Nothing"
- putChunks cert
- }
+ = C.fromList
+ [ ( GET
+ , do setContentType [mimeType| text/plain |]
+ putChunk "getRemoteCertificate = "
+ cert ← do cert ← getRemoteCertificate
+ case cert of
+ Just c → liftIO $ Lazy.pack <$> printX509 c
+ Nothing → return "Nothing"
+ putChunks cert
+ )
+ ]
genCert ∷ KeyPair k ⇒ k → IO X509
genCert pkey
setNotAfter cert =≪ addUTCTime (365 * 24 * 60 * 60) <$> getCurrentTime
setPublicKey cert pkey
signX509 cert pkey Nothing
- return cert
\ No newline at end of file
+ return cert