= do i ← openInput srcFile (getMIMEType opts) (getETag opts)
o ← openOutput opts
doc ← pprInput i modName symName
- hPutStrLn o $ show $ to_HPJ_Doc doc
+ hPutStrLn o ∘ show $ to_HPJ_Doc doc
hClose o
where
modName ∷ ModName
#if defined(HAVE_SSL)
import OpenSSL.Session
#endif
+import Prelude.Unicode
import System.IO.Unsafe
-- |Configuration record for to run the httpd.
defaultConfig ∷ Config
defaultConfig = Config {
cnfServerSoftware = "Lucu/1.0"
- , cnfServerHost = CI.mk $ T.pack $ unsafePerformIO getHostName
+ , cnfServerHost = CI.mk ∘ T.pack $ unsafePerformIO getHostName
, cnfServerPort = "http"
, cnfServerV4Addr = Just "0.0.0.0"
, cnfServerV6Addr = Just "::"
→ b ⇝ XmlTree
{-# INLINEABLE mkDefaultPage #-}
mkDefaultPage conf status msgA
- = let sStr = A.toString $ A.fromAsciiBuilder $ printStatusCode status
+ = let sStr = A.toString ∘ A.fromAsciiBuilder $ printStatusCode status
sig = concat [ A.toString (cnfServerSoftware conf)
, " at "
- , T.unpack $ CI.original $ cnfServerHost conf
+ , T.unpack ∘ CI.original $ cnfServerHost conf
]
in ( eelem "/"
+= ( eelem "html"
= none
where
path ∷ String
- path = uriPath $ reqURI $ fromJust req
+ path = uriPath ∘ reqURI $ fromJust req
loc ∷ String
- loc = A.toString $ fromJust $ getHeader "Location" res
+ loc = A.toString ∘ fromJust $ getHeader "Location" res
joinValues = A.fromAsciiBuilder
∘ mconcat
∘ intersperse (A.toAsciiBuilder "\x20")
- ∘ map A.toAsciiBuilder
+ ∘ (A.toAsciiBuilder <$>)
printHeaders ∷ Headers → AsciiBuilder
printHeaders (Headers m)
- = mconcat (map printHeader (fromFoldable m)) ⊕
+ = mconcat (printHeader <$> fromFoldable m) ⊕
A.toAsciiBuilder "\x0D\x0A"
where
printHeader ∷ (CIAscii, Ascii) → AsciiBuilder
import Network.HTTP.Lucu.Resource.Tree
import Network.HTTP.Lucu.ResponseWriter
import Network.HTTP.Lucu.SocketLike as SL
+import Prelude.Unicode
-- |This is the entry point of Lucu httpd. It listens to a socket and
-- waits for clients. 'runHttpd' never stops by itself so the only way
launchListener so
= do p ← SL.socketPort so
-- FIXME: Don't throw away the thread ID as we can't
- -- kill it later then. [1]
- void $ forkIO $ httpLoop p so
+ -- kill it later then.
+ void ∘ forkIO $ httpLoop p so
listenOn ∷ Family → HostName → ServiceName → IO Socket
listenOn fam host srv
unqualify ∷ Name → String → RewriteRule
unqualify (Name o _) m
= let pat = NamePat Nothing (Just o)
- iop = UnqualifiedImp (mkModName m)
- $ Just
+ iop = UnqualifiedImp (mkModName m) ∘ Just
$ singleton (VarName, o)
in
RewriteRule pat Unqualify (singleton iop)
unqualifyIn ∷ Name → Name → String → RewriteRule
unqualifyIn (Name name _) (Name tycl _) m
= let pat = NamePat Nothing (Just name)
- iop = UnqualifiedImp (mkModName m)
- $ Just
+ iop = UnqualifiedImp (mkModName m) ∘ Just
$ singleton (TcClsName, tycl)
in
RewriteRule pat Unqualify (singleton iop)
"linebreak"
compile ∷ Ord k ⇒ [(v, [k])] → Either (k, v, v) (Map k v)
-compile = go (∅) ∘ concat ∘ map tr
+compile = go (∅) ∘ concat ∘ (tr <$>)
where
tr ∷ (v, [k]) → [(k, v)]
tr (v, ks) = [(k, v) | k ← ks]
(
)
where
+import Control.Applicative hiding (empty)
import Data.Ascii (Ascii)
import qualified Data.Ascii as A
import Data.ByteString (ByteString)
import Prelude.Unicode
instance Lift ByteString where
- lift bs = [| Strict.pack $(litE $ stringL $ Strict.unpack bs) |]
+ lift bs = [| Strict.pack $(litE ∘ stringL $ Strict.unpack bs) |]
instance Lift Lazy.ByteString where
lift = Lazy.foldrChunks f [| Lazy.Empty |]
lift s = [| CI.mk $(lift $ CI.original s) |]
instance Lift Text where
- lift t = [| T.pack $(litE $ stringL $ T.unpack t) |]
+ lift t = [| T.pack $(litE ∘ stringL $ T.unpack t) |]
instance (Lift k, Lift v, Collection c (k, v)) ⇒ Lift c where
lift c
| null c = [| empty |]
| otherwise = [| fromList $(liftPairs (fromFoldable c)) |]
where
- liftPairs = listE ∘ map liftPair
+ liftPairs = listE ∘ (liftPair <$>)
liftPair (k, v) = tupE [lift k, lift v]
instance Lift UTCTime where
lift dt = [| fromRational ($n % $d) ∷ DiffTime |]
where
n, d ∷ Q Exp
- n = lift $ numerator $ toRational dt
- d = lift $ denominator $ toRational dt
+ n = lift ∘ numerator $ toRational dt
+ d = lift ∘ denominator $ toRational dt
quotedStr = do void $ char '"'
xs ← P.many (qdtext <|> quotedPair)
void $ char '"'
- return $ A.unsafeFromByteString $ BS.pack xs
+ return ∘ A.unsafeFromByteString $ BS.pack xs
<?>
"quotedStr"
where
)
where
unescape ∷ String → ByteString
- unescape = Strict.pack ∘ unEscapeString ∘ map plusToSpace
+ unescape = Strict.pack ∘ unEscapeString ∘ (plusToSpace <$>)
plusToSpace ∷ Char → Char
plusToSpace '+' = ' '
= let reqPathStr = uriPath uri
reqPath = [unEscapeString x | x ← splitBy (≡ '/') reqPathStr, (¬) (null x)]
in
- map Strict.pack reqPath
+ Strict.pack <$> reqPath
-- |>>> trim " ab c d "
-- "ab c d"
where
clockTimeToUTC ∷ ClockTime → UTCTime
clockTimeToUTC (TOD sec picoSec)
- = posixSecondsToUTCTime
- $ fromRational
+ = posixSecondsToUTCTime ∘ fromRational
$ sec % 1 + picoSec % (1000 ⋅ 1000 ⋅ 1000 ⋅ 1000)