hlint
This commit is contained in:
parent
f8c157bb42
commit
48d8ac3085
@ -79,7 +79,7 @@ import Yesod.Content
|
||||
mkYesod :: String -- ^ name of the argument datatype
|
||||
-> [Resource]
|
||||
-> Q [Dec]
|
||||
mkYesod name = fmap (\(x, y) -> x ++ y) . mkYesodGeneral name [] [] False
|
||||
mkYesod name = fmap (uncurry (++)) . mkYesodGeneral name [] [] False
|
||||
|
||||
-- | Generates URL datatype and site function for the given 'Resource's. This
|
||||
-- is used for creating subsites, *not* sites. See 'mkYesod' for the latter.
|
||||
@ -91,7 +91,7 @@ mkYesodSub :: String -- ^ name of the argument datatype
|
||||
-> [Resource]
|
||||
-> Q [Dec]
|
||||
mkYesodSub name clazzes =
|
||||
fmap (\(x, y) -> x ++ y) . mkYesodGeneral name' rest clazzes True
|
||||
fmap (uncurry (++)) . mkYesodGeneral name' rest clazzes True
|
||||
where
|
||||
(name':rest) = words name
|
||||
|
||||
@ -134,7 +134,7 @@ mkYesodGeneral :: String -- ^ argument name
|
||||
mkYesodGeneral name args clazzes isSub res = do
|
||||
let name' = mkName name
|
||||
args' = map mkName args
|
||||
arg = foldl AppT (ConT $ name') $ map VarT args'
|
||||
arg = foldl AppT (ConT name') $ map VarT args'
|
||||
let site = mkName $ "site" ++ name
|
||||
let gsbod = NormalB $ VarE site
|
||||
let yes' = FunD (mkName "getSite") [Clause [] gsbod []]
|
||||
|
||||
@ -24,10 +24,9 @@ module Yesod.Formable
|
||||
import Text.Hamlet
|
||||
import Data.Time (Day)
|
||||
import Control.Applicative
|
||||
import Database.Persist (Persistable)
|
||||
import Database.Persist (Persistable, Table (..))
|
||||
import Data.Char (isAlphaNum, toUpper, isUpper)
|
||||
import Language.Haskell.TH.Syntax
|
||||
import Database.Persist (Table (..))
|
||||
import Control.Monad (liftM)
|
||||
import Control.Arrow (first)
|
||||
import Data.Maybe (fromMaybe, isJust)
|
||||
@ -134,7 +133,7 @@ wrapperRow label errs control = [$hamlet|
|
||||
%li $string.err$
|
||||
|]
|
||||
|
||||
instance Formable [Char] where
|
||||
instance Formable String where
|
||||
formable = input' go
|
||||
where
|
||||
go name val = [$hamlet|
|
||||
|
||||
@ -269,7 +269,7 @@ redirectParams rt url params = do
|
||||
| c == ' ' = "+"
|
||||
| otherwise = '%' : myShowHex (ord c) ""
|
||||
myShowHex :: Int -> ShowS
|
||||
myShowHex n r = case showIntAtBase 16 (toChrHex) n r of
|
||||
myShowHex n r = case showIntAtBase 16 toChrHex n r of
|
||||
[] -> "00"
|
||||
[c] -> ['0',c]
|
||||
s -> s
|
||||
|
||||
@ -155,7 +155,7 @@ crudHelper title me isPost = do
|
||||
|
||||
defaultCrud :: (Persist i (YesodDB a (GHandler (Crud a i) a)), YesodPersist a)
|
||||
=> a -> Crud a i
|
||||
defaultCrud = const $ Crud
|
||||
defaultCrud = const Crud
|
||||
{ crudSelect = runDB $ select [] []
|
||||
, crudReplace = \a -> runDB . replace a
|
||||
, crudInsert = runDB . insert
|
||||
|
||||
@ -95,7 +95,7 @@ jsonList (x:xs) = mconcat
|
||||
, Json $ preEscapedString "]"
|
||||
]
|
||||
where
|
||||
go j = mappend (Json $ preEscapedString ",") j
|
||||
go = mappend (Json $ preEscapedString ",")
|
||||
|
||||
-- | Outputs a JSON map, eg {\"foo\":\"bar\",\"baz\":\"bin\"}.
|
||||
jsonMap :: [(String, Json)] -> Json
|
||||
|
||||
Loading…
Reference in New Issue
Block a user