, unqualifyAll "Network.HTTP.Lucu.ETag" "Network.HTTP.Lucu"
, unqualifyAll "Network.HTTP.Lucu.Resource" "Network.HTTP.Lucu"
, unqualifyAll "Network.HTTP.Lucu.Resource.Internal" "Network.HTTP.Lucu"
- , unqualifyAll "Network.HTTP.Lucu.MIMEParams" "Network.HTTP.Lucu"
, unqualifyAll "Network.HTTP.Lucu.MIMEType" "Network.HTTP.Lucu"
, unqualify 'when "Control.Monad"
, unqualify 'mempty "Data.Monoid"
import Data.Monoid
import Data.Text (Text)
import Data.Typeable
+import Language.Haskell.TH.Syntax
+import Network.HTTP.Lucu.OrphanInstances ()
-- |A 'Map' from MIME parameter attributes to values. Attributes are
-- always case-insensitive according to RFC 2045
-- (<http://tools.ietf.org/html/rfc2045#section-5.1>).
newtype MIMEParams
= MIMEParams (M.Map CIAscii Text)
- deriving (Eq, Show, Read, Monoid, Typeable)
+ deriving (Eq, Show, Read, Lift, Monoid, Typeable)
{-# LANGUAGE
FlexibleContexts
, FlexibleInstances
- , OverlappingInstances
, RecordWildCards
+ , ScopedTypeVariables
, TemplateHaskell
- , UndecidableInstances
, UnicodeSyntax
#-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
import qualified Data.CaseInsensitive as CI
import Data.Collections
import Data.Collections.BaseInstances ()
+import qualified Data.Map as M
import Data.Ratio
import Data.Text (Text)
import qualified Data.Text as T
instance Lift Text where
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)) |]
+instance (Lift k, Lift v) ⇒ Lift (M.Map k v) where
+ lift m
+ | null m = [| empty |]
+ | otherwise = [| fromAscList $(liftPairs (M.toAscList m)) |]
where
- liftPairs = listE ∘ (liftPair <$>)
+ liftPairs ∷ [(k, v)] → Q Exp
+ liftPairs = listE ∘ (liftPair <$>)
+
+ liftPair ∷ (k, v) → Q Exp
liftPair (k, v) = tupE [lift k, lift v]
instance Lift UTCTime where
--- /dev/null
+--- !ditz.rubyforge.org,2008-03-06/issue
+title: Remove deps on HXT
+desc: It's an overkill to use HXT to generate default pages.
+type: :task
+component: Lucu
+release: Lucu-1.0
+reporter: PHO <pho@cielonegro.org>
+status: :unstarted
+disposition:
+creation_time: 2011-11-29 12:14:42.124430 Z
+references: []
+
+id: ce71be0bc848dbefccc5cea88e5c9339083d97ee
+log_events:
+- - 2011-11-29 12:14:43.052342 Z
+ - PHO <pho@cielonegro.org>
+ - created
+ - ""
+git_branch:
Implanted.hs: dist/MiseRafturai.hs
dist/MiseRafturai.hs: mise-rafturai.html $(IMPLANT)
mkdir -p dist
- $(IMPLANT) -m MiseRafturai -o $@ $<
+ $(IMPLANT) -m MiseRafturai -o $@ $< || (rm -f $@; exit 1)
ImplantedSmall.hs: dist/SmallFile.hs
dist/SmallFile.hs: small-file.txt $(IMPLANT)
mkdir -p dist
- $(IMPLANT) -m SmallFile -t "text/plain; charset=\"UTF-8\"" -o $@ $<
+ $(IMPLANT) -m SmallFile -t "text/plain; charset=\"UTF-8\"" -o $@ $< || (rm -f $@; exit 1)
.PHONY: build run clean