TemplateHaskell
, UnicodeSyntax
#-}
--- |FIXME: doc
+-- |Doesn't anyone know why these instances can't be derived using
+-- GeneralizedNewtypeDeriving? I think its limitation isn't reasonable
+-- at all...
module Data.Collections.Newtype.TH
( derive
)
type Deriver = Q Cxt → Q Type → Q Exp → Q Exp → Q Dec
--- |FIXME: doc
+-- |Automatic newtype instance deriver for type classes defined by the
+-- collections-api package.
+--
+-- @
+-- {-\# LANGUAGE TemplateHaskell \#-}
+-- module Foo (T) where
+-- import "Data.Collections"
+-- import "Data.Collections.BaseInstances" ()
+-- import qualified Data.Collections.Newtype.TH as C
+-- import qualified "Data.Map" as M
+--
+-- newtype T = T (M.Map 'Int' 'Bool')
+--
+-- C.derive [d| instance 'Unfoldable' T ('Int', 'Bool')
+-- instance 'Foldable' T ('Int', 'Bool')
+-- instance 'Indexed' T 'Int' 'Bool'
+-- ...
+-- |]
+-- @
+--
+-- This function can derive the following instances:
+--
+-- * 'Unfoldable'
+--
+-- * 'Foldable'
+--
+-- * 'Collection'
+--
+-- * 'Indexed'
+--
+-- * 'Map'
+--
+-- * 'Set'
+--
+-- * 'SortingCollection'
+--
derive ∷ Q [Dec] → Q [Dec]
derive = (concat <$>) ∘ (mapM go =≪)
where
-DHAVE_SSL
Exposed-Modules:
+ Data.Collections.Newtype.TH
Network.HTTP.Lucu
Network.HTTP.Lucu.Abortion
Network.HTTP.Lucu.Authentication
Network.HTTP.Lucu.Utils
Other-Modules:
- Data.Collections.Newtype.TH
Network.HTTP.Lucu.Abortion.Internal
Network.HTTP.Lucu.Chunk
Network.HTTP.Lucu.ContentCoding
--
-- Example:
--
--- > {-# LANGUAGE OverloadedStrings #-}
--- > {-# LANGUAGE QuasiQuotes #-}
--- > module Main where
--- > import Network
--- > import Network.HTTP.Lucu
--- >
--- > main :: IO ()
--- > main = let config = defaultConfig
--- > resources = mkResTree [ ([], helloWorld) ]
--- > in
--- > withSocketsDo $ runHttpd config resourcees []
--- >
--- > helloWorld :: Resource
--- > helloWorld = emptyResource {
--- > resGet
--- > = Just $ do setContentType [mimeType| text/plain |]
--- > putChunk "Hello, world!"
--- > }
+-- @
+-- {-\# LANGUAGE OverloadedStrings \#-}
+-- {-\# LANGUAGE QuasiQuotes \#-}
+-- module Main where
+-- import qualified "Data.Collections" as C
+-- import "Network"
+-- import "Network.HTTP.Lucu"
--
--- FIXME: update the above example
+-- main :: 'IO' ()
+-- main = let config = 'defaultConfig'
+-- tree :: 'ResourceTree'
+-- tree = C.fromList [ ([], 'nonGreedy' helloWorld) ]
+-- in
+-- 'Network.withSocketsDo' '$' 'runHttpd' config '$' 'resourceMap' tree
+--
+-- helloWorld :: 'Network.HTTP.Lucu.Resource'
+-- helloWorld = C.fromList
+-- [ ( 'Network.HTTP.Lucu.GET'
+-- , do 'Network.HTTP.Lucu.setContentType' ['Network.HTTP.Lucu.mimeType'| text/plain |]
+-- 'Network.HTTP.Lucu.putChunk' \"Hello, world!\"
+-- }
+-- @
runHttpd ∷ HostMapper α ⇒ Config → α → IO ()
runHttpd cnf hm
= do let launchers
import qualified Data.ByteString.Lazy.Char8 as Lazy
import qualified Data.Collections as C
import Data.Monoid.Unicode
+import Network
import Network.HTTP.Lucu
import Prelude.Unicode
| otherwise = Nothing
in
do putStrLn "Access http://localhost:9999/ with your browser."
- runHttpd config mapper
+ withSocketsDo $ runHttpd config mapper
helloWorld ∷ Resource
helloWorld = C.fromList
#-}
import qualified Data.Collections as C
import MiseRafturai
+import Network
import Network.HTTP.Lucu
main ∷ IO ()
tree = C.fromList [ ([], nonGreedy miseRafturai) ]
in
do putStrLn "Access http://localhost:9999/ with your browser."
- runHttpd config $ resourceMap tree
+ withSocketsDo $ runHttpd config $ resourceMap tree
UnicodeSyntax
#-}
import qualified Data.Collections as C
+import Network
import Network.HTTP.Lucu
import SmallFile
tree = C.fromList [ ([], nonGreedy smallFile) ]
in
do putStrLn "Access http://localhost:9999/ with your browser."
- runHttpd config $ resourceMap tree
+ withSocketsDo $ runHttpd config $ resourceMap tree
import Control.Monad.Unicode
import Data.Maybe
import Data.Monoid.Unicode
+import Network
import Network.HTTP.Lucu
main ∷ IO ()
tree = C.fromList [ ([], nonGreedy resMain) ]
in
do putStrLn "Access http://localhost:9999/ with your browser."
- runHttpd config $ resourceMap tree
+ withSocketsDo $ runHttpd config $ resourceMap tree
resMain ∷ Resource
resMain = C.fromList
import qualified Data.ByteString.Lazy.Char8 as Lazy
import qualified Data.Collections as C
import Data.Time.Clock
+import Network
import Network.HTTP.Lucu
import OpenSSL
import OpenSSL.EVP.PKey
tree ∷ ResourceTree
tree = C.fromList [ ([], nonGreedy helloWorld) ]
putStrLn "Access https://localhost:9001/ with your browser."
- runHttpd config $ resourceMap tree
+ withSocketsDo $ runHttpd config $ resourceMap tree
helloWorld ∷ Resource
helloWorld