summaryrefslogtreecommitdiff
path: root/standalone/android/haskell-patches/yesod-static-1.1.2-remove-TH.patch
blob: de30ea4ca11172fdcc0e2cac17c767e2d7f4d356 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
From 476414b04064bb66fc25ba9ca426c309fe5c156e Mon Sep 17 00:00:00 2001
From: Joey Hess <joey@kitenet.net>
Date: Mon, 15 Apr 2013 12:48:13 -0400
Subject: [PATCH] remove TH

---
 Yesod/Static.hs           | 121 ----------------------------------------------
 dist/package.conf.inplace |   3 +-
 2 files changed, 2 insertions(+), 122 deletions(-)

diff --git a/Yesod/Static.hs b/Yesod/Static.hs
index e8ca09f..193b1f0 100644
--- a/Yesod/Static.hs
+++ b/Yesod/Static.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE FlexibleInstances #-}
@@ -34,11 +32,6 @@ module Yesod.Static
       -- * Smart constructor
     , static
     , staticDevel
-    , embed
-      -- * Template Haskell helpers
-    , staticFiles
-    , staticFilesList
-    , publicFiles
       -- * Hashing
     , base64md5
 #ifdef TEST_EXPORT
@@ -50,7 +43,6 @@ import Prelude hiding (FilePath)
 import qualified Prelude
 import System.Directory
 import Control.Monad
-import Data.FileEmbed (embedDir)
 
 import Yesod.Core hiding (lift)
 
@@ -111,18 +103,6 @@ staticDevel dir = do
     hashLookup <- cachedETagLookupDevel dir
     return $ Static $ webAppSettingsWithLookup (F.decodeString dir) hashLookup
 
--- | Produce a 'Static' based on embedding all of the static
--- files' contents in the executable at compile time.
--- Nota Bene: if you replace the scaffolded 'static' call in Settings/StaticFiles.hs
--- you will need to change the scaffolded addStaticContent.  Otherwise, some of your
--- assets will be 404'ed.  This is because by default yesod will generate compile those
--- assets to @static/tmp@ which for 'static' is fine since they are served out of the 
--- directory itself.  With embedded static, that will not work.  
--- You can easily change @addStaticContent@ to @\_ _ _ -> return Nothing@ as a workaround.
--- This will cause yesod to embed those assets into the generated HTML file itself.  
-embed :: Prelude.FilePath -> Q Exp
-embed fp = [|Static (embeddedSettings $(embedDir fp))|]
-
 instance RenderRoute Static where
     -- | A route on the static subsite (see also 'staticFiles').
     --
@@ -167,59 +147,6 @@ getFileListPieces = flip go id
         dirs' <- mapM (\f -> go (fullPath f) (front . (:) f)) dirs
         return $ concat $ files' : dirs'
 
--- | Template Haskell function that automatically creates routes
--- for all of your static files.
---
--- For example, if you used
---
--- > staticFiles "static/"
---
--- and you had files @\"static\/style.css\"@ and
--- @\"static\/js\/script.js\"@, then the following top-level
--- definitions would be created:
---
--- > style_css    = StaticRoute ["style.css"]    []
--- > js_script_js = StaticRoute ["js/script.js"] []
---
--- Note that dots (@.@), dashes (@-@) and slashes (@\/@) are
--- replaced by underscores (@\_@) to create valid Haskell
--- identifiers.
-staticFiles :: Prelude.FilePath -> Q [Dec]
-staticFiles dir = mkStaticFiles dir
-
--- | Same as 'staticFiles', but takes an explicit list of files
--- to create identifiers for. The files path given are relative
--- to the static folder. For example, to create routes for the
--- files @\"static\/js\/jquery.js\"@ and
--- @\"static\/css\/normalize.css\"@, you would use:
---
--- > staticFilesList \"static\" [\"js\/jquery.js\", \"css\/normalize.css\"]
---
--- This can be useful when you have a very large number of static
--- files, but only need to refer to a few of them from Haskell.
-staticFilesList :: Prelude.FilePath -> [Prelude.FilePath] -> Q [Dec]
-staticFilesList dir fs =
-    mkStaticFilesList dir (map split fs) "StaticRoute" True
-  where
-    split :: Prelude.FilePath -> [String]
-    split [] = []
-    split x =
-        let (a, b) = break (== '/') x
-         in a : split (drop 1 b)
-
--- | Same as 'staticFiles', but doesn't append an ETag to the
--- query string.
---
--- Using 'publicFiles' will speed up the compilation, since there
--- won't be any need for hashing files during compile-time.
--- However, since the ETag ceases to be part of the URL, the
--- 'Static' subsite won't be able to set the expire date too far
--- on the future.  Browsers still will be able to cache the
--- contents, however they'll need send a request to the server to
--- see if their copy is up-to-date.
-publicFiles :: Prelude.FilePath -> Q [Dec]
-publicFiles dir = mkStaticFiles' dir "StaticRoute" False
-
 
 mkHashMap :: Prelude.FilePath -> IO (M.Map F.FilePath S8.ByteString)
 mkHashMap dir = do
@@ -262,54 +189,6 @@ cachedETagLookup dir = do
     etags <- mkHashMap dir
     return $ (\f -> return $ M.lookup f etags)
 
-mkStaticFiles :: Prelude.FilePath -> Q [Dec]
-mkStaticFiles fp = mkStaticFiles' fp "StaticRoute" True
-
-mkStaticFiles' :: Prelude.FilePath -- ^ static directory
-               -> String   -- ^ route constructor "StaticRoute"
-               -> Bool     -- ^ append checksum query parameter
-               -> Q [Dec]
-mkStaticFiles' fp routeConName makeHash = do
-    fs <- qRunIO $ getFileListPieces fp
-    mkStaticFilesList fp fs routeConName makeHash
-
-mkStaticFilesList
-    :: Prelude.FilePath -- ^ static directory
-    -> [[String]] -- ^ list of files to create identifiers for
-    -> String   -- ^ route constructor "StaticRoute"
-    -> Bool     -- ^ append checksum query parameter
-    -> Q [Dec]
-mkStaticFilesList fp fs routeConName makeHash = do
-    concat `fmap` mapM mkRoute fs
-  where
-    replace' c
-        | 'A' <= c && c <= 'Z' = c
-        | 'a' <= c && c <= 'z' = c
-        | '0' <= c && c <= '9' = c
-        | otherwise = '_'
-    mkRoute f = do
-        let name' = intercalate "_" $ map (map replace') f
-            routeName = mkName $
-                case () of
-                    ()
-                        | null name' -> error "null-named file"
-                        | isDigit (head name') -> '_' : name'
-                        | isLower (head name') -> name'
-                        | otherwise -> '_' : name'
-        f' <- [|map pack $(lift f)|]
-        let route = mkName routeConName
-        pack' <- [|pack|]
-        qs <- if makeHash
-                    then do hash <- qRunIO $ base64md5File $ pathFromRawPieces fp f
-                            [|[(pack "etag", pack $(lift hash))]|]
-                    else return $ ListE []
-        return
-            [ SigD routeName $ ConT route
-            , FunD routeName
-                [ Clause [] (NormalB $ (ConE route) `AppE` f' `AppE` qs) []
-                ]
-            ]
-
 base64md5File :: Prelude.FilePath -> IO String
 base64md5File = fmap (base64 . encode) . hashFile
     where encode d = Data.Serialize.encode (d :: MD5)
diff --git a/dist/package.conf.inplace b/dist/package.conf.inplace
index 0637a08..eeff311 100644
--- a/dist/package.conf.inplace
+++ b/dist/package.conf.inplace
@@ -1 +1,2 @@
-[]
\ No newline at end of file
+[InstalledPackageInfo {installedPackageId = InstalledPackageId "yesod-static-1.1.2-inplace", sourcePackageId = PackageIdentifier {pkgName = PackageName "yesod-static", pkgVersion = Version {versionBranch = [1,1,2], versionTags = []}}, license = MIT, copyright = "", maintainer = "Michael Snoyman <michael@snoyman.com>, Greg Weber <greg@gregweber.info>", author = "Michael Snoyman <michael@snoyman.com>", stability = "Stable", homepage = "http://www.yesodweb.com/", pkgUrl = "", synopsis = "Static file serving subsite for Yesod Web Framework.", description = "Static file serving subsite for Yesod Web Framework.", category = "Web, Yesod", exposed = True, exposedModules = ["Yesod.Static"], hiddenModules = [], trusted = False, importDirs = ["/home/joey/yesod-static-1.1.2/dist/build"], libraryDirs = ["/home/joey/yesod-static-1.1.2/dist/build"], hsLibraries = ["HSyesod-static-1.1.2"], extraLibraries = [], extraGHCiLibraries = [], includeDirs = [], includes = [], depends = [InstalledPackageId "base-4.7.0.0-460992ac16ead97d88c73f4125e796d4",InstalledPackageId "base64-bytestring-1.0.0.1-8f54bb73ec493a5130061ebca542c11e",InstalledPackageId "bytestring-0.10.3.0-9c590669208a87636c23a3d3510a31ff",InstalledPackageId "cereal-0.3.5.2-f30c5cc09d1cc15977a64fe292c53513",InstalledPackageId "conduit-0.5.6-3168abc5ff00ded4bbc15f5915ad8633",InstalledPackageId "containers-0.5.0.0-eaa71ab98116fcd2d322913214739de5",InstalledPackageId "crypto-conduit-0.4.3-7a2968522a5c4748ce5988a2a466061e",InstalledPackageId "cryptohash-0.8.3-0aac68aa3a568ebeb89a354c921feb58",InstalledPackageId "directory-1.2.0.1-ca44c33c2fac281048d0dd7cd29e86c3",InstalledPackageId "file-embed-0.0.4.7-70a8411da82b83a0bbea9ecb291922ca",InstalledPackageId "http-types-0.7.3.0.1-09ea63b109c64a8370a96ee561c3ab2a",InstalledPackageId "old-time-1.1.0.1-9c370bbecb794b4c05408eb17a0038f1",InstalledPackageId "system-filepath-0.4.7-9506cbec38ccb0e49fd3a1dcce66306e",InstalledPackageId "template-haskell-2.9.0.0-60ba2293ffcafe171e54a808fdce5a7c",InstalledPackageId "text-0.11.2.3-948bb4afd264a1a5c0cca04031b4151c",InstalledPackageId "transformers-0.3.0.0-bae5adc5a648f25bafc73de9dc6a08a0",InstalledPackageId "unix-compat-0.4.1.0-0019b5bc860083c9a153099b086619ed",InstalledPackageId "wai-1.3.0.2-0f2b7cd8b8b0d8a776528af2b9f1f4f9",InstalledPackageId "wai-app-static-1.3.1-a32981caae981238524cee9823ccc666",InstalledPackageId "yesod-core-1.1.8-c0a15bfed9cb8f978bdf71ddd343ea18"], hugsOptions = [], ccOptions = [], ldOptions = [], frameworkDirs = [], frameworks = [], haddockInterfaces = ["/home/joey/yesod-static-1.1.2/dist/doc/html/yesod-static/yesod-static.haddock"], haddockHTMLs = ["/home/joey/yesod-static-1.1.2/dist/doc/html/yesod-static"]}
+]
\ No newline at end of file
-- 
1.8.2.rc3