diff --git a/Web/Mime.hs b/Web/Mime.hs
index 7c69e154..d774e32c 100644
--- a/Web/Mime.hs
+++ b/Web/Mime.hs
@@ -24,8 +24,6 @@ import Test.Framework (testGroup, Test)
import Test.Framework.Providers.HUnit
import Test.Framework.Providers.QuickCheck2 (testProperty)
import Test.HUnit hiding (Test)
-import Test.QuickCheck
-import Control.Monad (when)
#endif
-- | Equality is determined by converting to a 'String' via
diff --git a/Yesod/Json.hs b/Yesod/Json.hs
index 860d00e3..c6fe8e02 100644
--- a/Yesod/Json.hs
+++ b/Yesod/Json.hs
@@ -29,11 +29,8 @@ import Yesod.Content
#if TEST
import Test.Framework (testGroup, Test)
import Test.Framework.Providers.HUnit
-import Test.Framework.Providers.QuickCheck2 (testProperty)
import Test.HUnit hiding (Test)
-import Test.QuickCheck
import Data.Text.Lazy (unpack)
-import qualified Data.Text as T
#endif
newtype Json url a = Json { unJson :: Hamlet url IO a }
@@ -93,9 +90,9 @@ caseSimpleOutput :: Assertion
caseSimpleOutput = do
let j = do
jsonMap
- [ (jsonScalar $ T.pack "foo" , jsonList
- [ jsonScalar $ T.pack "bar"
- , jsonScalar $ T.pack "baz"
+ [ ("foo" , jsonList
+ [ jsonScalar $ Encoded $ pack "bar"
+ , jsonScalar $ Encoded $ pack "baz"
])
]
t <- hamletToText id $ unJson j
diff --git a/compile-examples.sh b/compile-examples.sh
deleted file mode 100755
index f037f0c4..00000000
--- a/compile-examples.sh
+++ /dev/null
@@ -1,6 +0,0 @@
-#!/bin/sh
-
-for f in examples/*.*hs
-do
- ghc --make -Wall -Werror $f || exit
-done
diff --git a/examples/fact.html b/examples/fact.html
deleted file mode 100644
index 4f849dd4..00000000
--- a/examples/fact.html
+++ /dev/null
@@ -1,30 +0,0 @@
-
-
-
- Factorials
-
-
-
-
-
-
-
-
diff --git a/examples/fact.lhs b/examples/fact.lhs
deleted file mode 100644
index 85af7b54..00000000
--- a/examples/fact.lhs
+++ /dev/null
@@ -1,106 +0,0 @@
-FIXME documentation is out of date in a few places.
-
-> {-# LANGUAGE QuasiQuotes #-}
-> {-# LANGUAGE TemplateHaskell #-}
-> {-# LANGUAGE TypeFamilies #-}
-
-I in general recommend type signatures for everything. However, I wanted
-to show in this example how it is possible to get away without the
-signatures.
-
-> {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
-
-There are only two imports: Yesod includes all of the code we need for creating
-a web application, while Network.Wai.Handler.SimpleServer allows us to test our
-application easily. A Yesod app can in general run on any WAI handler, so this
-application is easily convertible to CGI, FastCGI, or even run on the Happstack
-server.
-
-> import Yesod
-> import Network.Wai.Handler.SimpleServer
-
-The easiest way to start writing a Yesod app is to follow the Yesod typeclass.
-You define some data type which will contain all the specific settings and data
-you want in your application. This might include database connections,
-templates, etc. It's entirely up to you.
-
-For our simple demonstration, we need no extra data, so we simply define Fact
-as:
-
-> data Fact = Fact
-
-Now we need to declare an instance of Yesod for Fact. The most important
-function to declare is handlers, which defines which functions deal with which
-resources (aka URLs).
-
-You can declare the function however you want, but Yesod.Resource declares a
-convenient "resources" quasi-quoter which takes YAML content and generates the
-function for you. There is a lot of cool stuff to do with representations going
-on here, but this is not the appropriate place to discuss it.
-
-
-
-The structure is very simply: top level key is a "resource pattern". A resource pattern is simply a bunch of slash-separated strings, called "resource pattern pieces". There are three special ways to start a piece:
-
-* $: will take any string
-
-* \#: will take any integer
-
-* \*: will "slurp" up all the remaining pieces. Useful for something like
- /static/*filepath
-
-Otherwise, the piece is treated as a literal string which must be matched.
-
-
-Now we have a mapping of verbs to handler functions. We could instead simply
-specify a single function which handles all verbs. (Note: a verb is just a
-request method.)
-
-> $(mkYesod "Fact" [$parseRoutes|
-> / Index GET
-> /#num FactR GET
-> /fact FactRedirect GET
-> |])
-
-> instance Yesod Fact where
-> approot _ = "http://localhost:3000"
-
-This does what it looks like: serves a static HTML file.
-
-> getIndex = sendFile TypeHtml "examples/fact.html" >> return ()
-
-HtmlObject is a funny beast. Basically, it allows multiple representations of
-data, all with HTML entities escaped properly. These representations include:
-
-* Simple HTML document (only recommended for testing).
-* JSON (great for Ajax)
-* Input to a HStringTemplate (great for no-Javascript fallback).
-
-For simplicity here, we don't include a template, though it would be trivial to
-do so (see the hellotemplate example).
-
-> getFactR :: Integer -> Handler y ChooseRep -- FIXME remove
-> getFactR _i = error "FIXME" {-simpleApplyLayout "Factorial result" $ cs
-> [ ("input", show i)
-> , ("result", show $ product [1..fromIntegral i :: Integer])
-> ]-}
-
-I've decided to have a redirect instead of serving the some data in two
-locations. It fits in more properly with the RESTful principal of one name for
-one piece of data.
-
-> getFactRedirect :: Handler y ()
-> getFactRedirect = do
-> res <- runFormPost $ catchFormError
-> $ checkInteger
-> $ required
-> $ input "num"
-> let i = either (const "1") show res
-> redirect RedirectPermanent $ "../" ++ i ++ "/"
-
-You could replace this main to use any WAI handler you want. For production,
-you could use CGI, FastCGI or a more powerful server. Just check out Hackage
-for options (any package starting hack-handler- should suffice).
-
-> main :: IO ()
-> main = putStrLn "Running..." >> toWaiApp Fact >>= run 3000
diff --git a/examples/hamlet.hs b/examples/hamlet.hs
deleted file mode 100644
index 447bf5dd..00000000
--- a/examples/hamlet.hs
+++ /dev/null
@@ -1,38 +0,0 @@
-{-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE TypeFamilies #-}
-
-import Yesod
-import Network.Wai.Handler.SimpleServer
-
-data Ham = Ham
-
-mkYesod "Ham" [$parseRoutes|
-/ Homepage GET
-/#another Another GET
-|]
-
-instance Yesod Ham where
- approot _ = "http://localhost:3000"
-
-data NextLink = NextLink { nextLink :: HamRoutes }
-
-template :: Monad m => NextLink -> Hamlet HamRoutes m ()
-template = [$hamlet|
-%a!href=@nextLink@ Next page
-|]
-
-getHomepage :: Handler Ham RepHtml
-getHomepage = hamletToRepHtml $ template $ NextLink $ Another 1
-
-getAnother :: Integer -> Handler Ham RepHtml
-getAnother i = hamletToRepHtml $ template $ NextLink next
- where
- next = case i of
- 5 -> Homepage
- _ -> Another $ i + 1
-
-main :: IO ()
-main = do
- putStrLn "Running..."
- toWaiApp Ham >>= run 3000
diff --git a/examples/helloworld.lhs b/examples/helloworld.lhs
deleted file mode 100644
index cf889531..00000000
--- a/examples/helloworld.lhs
+++ /dev/null
@@ -1,23 +0,0 @@
-\begin{code}
-{-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE TypeFamilies #-}
-
-import Yesod
-import Network.Wai.Handler.SimpleServer
-
-data HelloWorld = HelloWorld
-
-mkYesod "HelloWorld" [$parseRoutes|
-/ Home GET
-|]
-
-instance Yesod HelloWorld where
- approot _ = "http://localhost:3000"
-
-getHome :: Handler HelloWorld RepHtml
-getHome = simpleApplyLayout "Hello World" $ cs "Hello world!"
-
-main :: IO ()
-main = putStrLn "Running..." >> toWaiApp HelloWorld >>= run 3000
-\end{code}
diff --git a/examples/i18n.hs b/examples/i18n.hs
deleted file mode 100644
index ae0651d4..00000000
--- a/examples/i18n.hs
+++ /dev/null
@@ -1,36 +0,0 @@
-{-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE TypeFamilies #-}
-
-import Yesod
-import Network.Wai.Handler.SimpleServer
-
-data I18N = I18N
-
-mkYesod "I18N" [$parseRoutes|
-/ Homepage GET
-/set/$lang SetLang GET
-|]
-
-instance Yesod I18N where
- approot _ = "http://localhost:3000"
-
-getHomepage :: Handler y [(ContentType, Content)]
-getHomepage = do
- ls <- languages
- let hello = chooseHello ls
- return [(TypePlain, cs hello :: Content)]
-
-chooseHello :: [Language] -> String
-chooseHello [] = "Hello"
-chooseHello ("he":_) = "שלום"
-chooseHello ("es":_) = "Hola"
-chooseHello (_:rest) = chooseHello rest
-
-getSetLang :: String -> Handler y ()
-getSetLang lang = do
- addCookie 1 langKey lang
- redirect RedirectTemporary "/"
-
-main :: IO ()
-main = putStrLn "Running..." >> toWaiApp I18N >>= run 3000
diff --git a/examples/pretty-yaml.hs b/examples/pretty-yaml.hs
deleted file mode 100644
index 1054936b..00000000
--- a/examples/pretty-yaml.hs
+++ /dev/null
@@ -1,67 +0,0 @@
-{-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE TypeFamilies #-}
-
-import Yesod
-import Data.Object.Yaml
-import Network.Wai.Handler.SimpleServer
-import Web.Encodings
-import qualified Data.ByteString as B
-import qualified Data.ByteString.Lazy as L
-import Data.Object.String
-
-data PY = PY
-
-mkYesod "PY" [$parseRoutes|
-/ Homepage GET POST
-|]
-
-instance Yesod PY where
- approot _ = "http://localhost:3000"
-
-template :: Monad m => TempArgs url m -> Hamlet url m ()
-template = [$hamlet|
-!!!
-%html
- %head
- %meta!charset=utf-8
- %title Pretty YAML
- %body
- %form!method=post!action=.!enctype=multipart/form-data
- File name:
- %input!type=file!name=yaml
- %input!type=submit
- $if hasYaml
- %div ^yaml^
-|]
-
-data TempArgs url m = TempArgs
- { hasYaml :: Bool
- , yaml :: Hamlet url m ()
- }
-
-getHomepage :: Handler PY RepHtml
-getHomepage = hamletToRepHtml
- $ template $ TempArgs False (return ())
-
---FIXMEpostHomepage :: Handler PY RepHtmlJson
-postHomepage :: Handler PY RepHtml
-postHomepage = do
- rr <- getRequest
- (_, files) <- liftIO $ reqRequestBody rr
- fi <- case lookup "yaml" files of
- Nothing -> invalidArgs [("yaml", "Missing input")]
- Just x -> return x
- so <- liftIO $ decode $ B.concat $ L.toChunks $ fileContent fi
- {- FIXME
- let ho' = fmap Text to
- templateHtmlJson "pretty-yaml" ho' $ \ho ->
- return . setHtmlAttrib "yaml" (Scalar $ cs ho :: HtmlObject)
- -}
- let ho = cs (so :: StringObject) :: HtmlObject
- hamletToRepHtml $ template $ TempArgs True (cs ho)
-
-main :: IO ()
-main = do
- putStrLn "Running..."
- toWaiApp PY >>= run 3000
diff --git a/examples/pretty-yaml.st b/examples/pretty-yaml.st
deleted file mode 100644
index 68e1e604..00000000
--- a/examples/pretty-yaml.st
+++ /dev/null
@@ -1,16 +0,0 @@
-
-
-
-
-Pretty YAML
-
-
-
-$if(yaml)$
-$yaml$
-$endif$
-
-
diff --git a/examples/real-template.st b/examples/real-template.st
deleted file mode 100644
index 17161eeb..00000000
--- a/examples/real-template.st
+++ /dev/null
@@ -1,3 +0,0 @@
-This is a more realistic template.
-foo: $foo$
-This is the default argument: $default$
diff --git a/examples/static.hs b/examples/static.hs
deleted file mode 100644
index 670d0a94..00000000
--- a/examples/static.hs
+++ /dev/null
@@ -1,25 +0,0 @@
-{-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE TypeFamilies #-}
-{-# OPTIONS_GHC -fno-warn-overlapping-patterns #-} -- FIXME due to bug in Hamlet
-
-import Yesod
-import Yesod.Helpers.Static
-import Network.Wai.Handler.SimpleServer
-
-data StaticExample = StaticExample
-
-mkYesod "StaticExample" [$parseRoutes|
-/ Root StaticRoutes siteStatic getStaticSite
-|]
-
-instance Yesod StaticExample where
- approot _ = "http://localhost:3000"
-
-getStaticSite :: StaticExample -> Static
-getStaticSite _ = fileLookupDir "dist/doc/html/yesod"
-
-main :: IO ()
-main = do
- putStrLn "Running..."
- toWaiApp StaticExample >>= run 3000
diff --git a/examples/template.st b/examples/template.st
deleted file mode 100644
index f71953cf..00000000
--- a/examples/template.st
+++ /dev/null
@@ -1,26 +0,0 @@
-
-
-
-
- $title$
-
-
-
-
- $content$
-
-
-
diff --git a/examples/tweedle-templates/category-details.st b/examples/tweedle-templates/category-details.st
deleted file mode 100644
index 0c3bdecb..00000000
--- a/examples/tweedle-templates/category-details.st
+++ /dev/null
@@ -1,27 +0,0 @@
-$layout(
- title={Category $name$};
- content={
-
-$name$
-
-
-Sub categories
-
-
-
-Issues
-
-| Title | Status | Priority |
-$cat.issues:{issue|
-| $issue.name$ | $issue.status$ | $issue.priority$ |
-}$
-
-})$
diff --git a/examples/tweedle-templates/issue-details.st b/examples/tweedle-templates/issue-details.st
deleted file mode 100644
index eaca279a..00000000
--- a/examples/tweedle-templates/issue-details.st
+++ /dev/null
@@ -1,37 +0,0 @@
-$layout(
- title={Issue $issue.name$ -- Category $cat.name$};
- content={
-$issue.name$
-
-
-$if(ident)$
-