Removed some FIXMEs

This commit is contained in:
Michael Snoyman 2013-01-02 14:26:56 +02:00
parent 7c72f11b21
commit 617c1d724e
9 changed files with 1 additions and 70 deletions

View File

@ -127,7 +127,7 @@ instance Monoid (GWData a) where
data HandlerContents =
HCContent H.Status ChooseRep
| HCError ErrorResponse
| HCSendFile ContentType FilePath (Maybe W.FilePart) -- FIXME replace FilePath with opaque type from system-filepath?
| HCSendFile ContentType FilePath (Maybe W.FilePart)
| HCRedirect H.Status Text
| HCCreated Text
| HCWai W.Response

View File

@ -115,10 +115,6 @@ addSubWidget sub (GWidget w) = do
class ToWidget sub master a where
toWidget :: a -> GWidget sub master ()
-- FIXME At some point in the future, deprecate all the
-- addHamlet/Cassius/Lucius/Julius stuff. For the most part, toWidget* will be
-- sufficient. For somethings, like addLuciusMedia, create addCssUrlMedia.
type RY master = Route master -> [(Text, Text)] -> Text
-- | Newtype wrapper allowing injection of arbitrary content into CSS.

View File

@ -161,7 +161,6 @@ htmlField = Field
{ fieldParse = parseHelper $ Right . preEscapedText . sanitizeBalance
, fieldView = \theId name attrs val _isReq -> toWidget [hamlet|
$newline never
$# FIXME: There was a class="html" attribute, for what purpose?
<textarea id="#{theId}" name="#{name}" *{attrs}>#{showVal val}
|]
, fieldEnctype = UrlEncoded

View File

@ -271,7 +271,6 @@ renderTable, renderDivs, renderDivsNoLabels :: FormRender sub master a
renderTable aform fragment = do
(res, views') <- aFormToForm aform
let views = views' []
-- FIXME non-valid HTML
let widget = [whamlet|
$newline never
\#{fragment}

View File

@ -2,7 +2,6 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoMonomorphismRestriction #-} -- FIXME remove
-- | Some fields spiced up with jQuery UI.
module Yesod.Form.Jquery
( YesodJquery (..)

View File

@ -2,7 +2,6 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoMonomorphismRestriction #-} -- FIXME remove
{-# LANGUAGE CPP #-}
-- | Provide the user with a rich text editor.
module Yesod.Form.Nic

View File

@ -72,29 +72,3 @@ findOverlapNames =
(go' $ resourceTreeName x, go' $ resourceTreeName y)
where
go' = intercalate "/" . front . return
{-
-- n^2, should be a way to speed it up
findOverlaps :: [Resource a] -> [[Resource a]]
findOverlaps = go . map justPieces
where
justPieces :: Resource a -> ([Piece a], Resource a)
justPieces r@(Resource _ ps _) = (ps, r)
go [] = []
go (x:xs) = mapMaybe (mOverlap x) xs ++ go xs
mOverlap :: ([Piece a], Resource a) -> ([Piece a], Resource a) ->
Maybe [Resource a]
mOverlap _ _ = Nothing
{- FIXME mOverlap
mOverlap (Static x:xs, xr) (Static y:ys, yr)
| x == y = mOverlap (xs, xr) (ys, yr)
| otherwise = Nothing
mOverlap (MultiPiece _:_, xr) (_, yr) = Just (xr, yr)
mOverlap (_, xr) (MultiPiece _:_, yr) = Just (xr, yr)
mOverlap ([], xr) ([], yr) = Just (xr, yr)
mOverlap ([], _) (_, _) = Nothing
mOverlap (_, _) ([], _) = Nothing
mOverlap (_:xs, xr) (_:ys, yr) = mOverlap (xs, xr) (ys, yr)
-}
-}

View File

@ -331,35 +331,3 @@ base64 = map tr
tr '+' = '-'
tr '/' = '_'
tr c = c
{- FIXME
-- | Dispatch static route for a subsite
--
-- Subsites with static routes can't (yet) define Static routes the same way "master" sites can.
-- Instead of a subsite route:
-- /static StaticR Static getStatic
-- Use a normal route:
-- /static/*Strings StaticR GET
--
-- Then, define getStaticR something like:
-- getStaticR = getStaticHandler ($(mkEmbedFiles "static") typeByExt) StaticR
-- */ end CPP comment
getStaticHandler :: Static -> (StaticRoute -> Route sub) -> [String] -> GHandler sub y ChooseRep
getStaticHandler static toSubR pieces = do
toMasterR <- getRouteToMaster
toMasterHandler (toMasterR . toSubR) toSub route handler
where route = StaticRoute pieces []
toSub _ = static
staticSite = getSubSite :: Site (Route Static) (String -> Maybe (GHandler Static y ChooseRep))
handler = fromMaybe notFound $ handleSite staticSite (error "Yesod.Static: getSTaticHandler") route "GET"
-}
{-
calcHash :: Prelude.FilePath -> IO String
calcHash fname =
withBinaryFile fname ReadMode hashHandle
where
hashHandle h = do s <- L.hGetContents h
return $! base64md5 s
-}

View File

@ -10,9 +10,6 @@ module Build
, safeReadFile
) where
-- FIXME there's a bug when getFileStatus applies to a file
-- temporary deleted (e.g., Vim saving a file)
import Control.Applicative ((<|>), many, (<$>))
import qualified Data.Attoparsec.Text as A
import Data.Char (isSpace, isUpper)