Add an hlint makefile target and implement some suggestions.
runghc Setup.hs haddock --internal \
--executables \
--hyperlink-source
+
+hlint:
+ hlint --ignore="Use camelCase" \
+ --ignore="Redundant bracket" \
+ --color \
+ src
-- 3. etc.
--
listify :: [String] -> [String]
-listify items =
- zipWith (++) list_numbers items
+listify =
+ zipWith (++) list_numbers
where
list_numbers = map show_with_dot [1::Integer ..]
show_with_dot x = (show x) ++ ". "
get_status :: Integer -> IO B.ByteString
get_status status_id = do
- let uri = (status_url status_id)
- status <- (http_get uri)
- return status
+ let uri = status_url status_id
+ http_get uri
-- | Return's username's timeline.
get_user_timeline :: String -> IO B.ByteString
get_user_timeline username = do
- let uri = (user_timeline_url username)
- timeline <- (http_get uri)
- return timeline
+ let uri = user_timeline_url username
+ http_get uri
-- | Returns the JSON representing all of username's statuses that are
-- newer than last_status_id.
get_user_new_statuses :: String -> Integer -> IO B.ByteString
get_user_new_statuses username last_status_id = do
- let uri = (user_new_statuses_url username last_status_id)
- new_statuses <- (http_get uri)
- return new_statuses
+ let uri = user_new_statuses_url username last_status_id
+ http_get uri
-- | Retrieve a URL, or crash.
+{-# LANGUAGE NoMonomorphismRestriction #-}
+
-- | Functions and data for working with Twitter statuses.
module Twitter.Status
where
import Control.Applicative ((<$>), (<*>))
import Control.Monad (liftM)
import Data.Aeson ((.:), FromJSON(..), Value(Object))
-import Data.Maybe (catMaybes, isJust)
+import Data.Maybe (fromMaybe, mapMaybe, isJust)
import Data.Monoid (mempty)
import Data.String.Utils (join, splitWs)
import Data.Text (pack)
show_created_at :: Maybe TimeZone -> Status -> String
show_created_at mtz =
- (maybe "" id) . (fmap $ utc_time_to_rfc822 mtz) . created_at
+ (fromMaybe "") . (fmap $ utc_time_to_rfc822 mtz) . created_at
-- | Returns a nicely-formatted String representing the given 'Status'
-- object.
-- | Parse all usernames of the form \@username from a status.
parse_usernames_from_status :: Status -> [String]
parse_usernames_from_status status =
- catMaybes (map parse_username status_words)
+ mapMaybe parse_username status_words
where
status_words = splitWs (text status)