]> gitweb.michael.orlitzky.com - dead/harbl.git/commitdiff
Fix compilation errors and hlint suggestions.
authorMichael Orlitzky <michael@orlitzky.com>
Thu, 9 Jul 2015 06:30:25 +0000 (02:30 -0400)
committerMichael Orlitzky <michael@orlitzky.com>
Thu, 9 Jul 2015 06:30:25 +0000 (02:30 -0400)
src/Domain.hs
src/Main.hs
src/Pretty.hs

index 46c93061f3247c7710c202a530f8e9cd8f95bf30..87a63d9757f8bb2c6cfda6bac49651101a3153ab 100644 (file)
@@ -1,3 +1,5 @@
+{-# LANGUAGE DoAndIfThenElse #-}
+
 -- | The 'Domain' data type and its parser. A 'Domain' represents a
 --   name in the domain name system (DNS) as described by
 --   RFC1035. In particular, we enforce the restrictions from Section
@@ -19,18 +21,11 @@ where
 
 import Data.Char ( toLower )
 import Text.Parsec (
-  ParseError,
   (<|>),
-  alphaNum,
   char,
-  eof,
-  many1,
-  option,
   optionMaybe,
-  parse,
   string,
-  try,
-  unexpected )
+  try )
 import qualified Text.Parsec as Parsec ( digit, letter)
 import Text.Parsec.String ( Parser )
 
@@ -204,6 +199,7 @@ instance Pretty LdhStr where
 --
 --   As well as strings of them:
 --
+--   >>> import Text.Parsec ( parse )
 --   >>> pretty_print $ parse ldh_str "" "a0-b"
 --   a0-b
 --
@@ -228,6 +224,8 @@ ldh_str = try both <|> just_one
 --
 --   ==== _Examples_
 --
+--   >>> import Text.Parsec ( parse )
+--
 --   >>> let (Right r) = parse ldh_str "" "a"
 --   >>> last_ldh_str r
 --   LetDigHypLetDig (LetDigLetter (Letter 'a'))
@@ -251,6 +249,8 @@ last_ldh_str (LdhStrMultipleLdh _ x) = last_ldh_str x
 --
 --   ==== _Examples_
 --
+--   >>> import Text.Parsec ( parse )
+--
 --   >>> let (Right r) = parse ldh_str "" "a"
 --   >>> init_ldh_str r
 --   Nothing
@@ -280,6 +280,8 @@ init_ldh_str (LdhStrMultipleLdh h t) =
 --
 --   ==== _Examples_
 --
+--   >>> import Text.Parsec ( parse )
+--
 --   >>> let (Right r) = parse ldh_str "" "a"
 --   >>> length_ldh_str r
 --   1
@@ -317,7 +319,7 @@ instance Pretty LdhStrLetDig where
 --
 --   ==== _Examples_
 --
---   >>> import Text.Parsec ( parseTest )
+--   >>> import Text.Parsec ( parse, parseTest )
 --
 --   Make sure we can parse a single character:
 --
@@ -368,6 +370,8 @@ ldh_str_let_dig = do
 --
 --   ==== _Examples_
 --
+--   >>> import Text.Parsec ( parse )
+--
 --   >>> let (Right r) = parse ldh_str_let_dig "" "a"
 --   >>> length_ldh_str_let_dig r
 --   1
@@ -419,7 +423,7 @@ instance Pretty Label where
 --
 --   ==== _Examples_
 --
---   >>> import Text.Parsec ( parseTest )
+--   >>> import Text.Parsec ( parse, parseTest )
 --
 --   Make sure we can parse a single character:
 --
@@ -514,7 +518,7 @@ instance Pretty Subdomain where
 --
 --   ==== _Examples_
 --
---   >>> import Text.Parsec ( parseTest )
+--   >>> import Text.Parsec ( parse, parseTest )
 --
 --   Make sure we can parse a single character:
 --
@@ -544,7 +548,7 @@ subdomain = try both <|> just_one
     both :: Parser Subdomain
     both = do
       l <- label
-      char '.'
+      _ <- char '.'
       s <- subdomain
       let result = SubdomainMultipleLabel l s
       if (subdomain_has_equal_neighbors result)
@@ -560,6 +564,8 @@ subdomain = try both <|> just_one
 --
 --   ==== _Examples_
 --
+--   >>> import Text.Parsec ( parse )
+--
 --   >>> let (Right r) = parse subdomain "" "a"
 --   >>> pretty_print $ subdomain_labels r
 --   ["a"]
@@ -581,6 +587,7 @@ subdomain_labels (SubdomainMultipleLabel l s) = l : (subdomain_labels s)
 --
 --   ==== _Examples_
 --
+--   >>> import Text.Parsec ( parse )
 --   >>> let (Right r) = parse subdomain "" "www.example.com"
 --   >>> pretty_print $ subdomain_label_neighbors r
 --   ["(\"www\",\"example\")","(\"example\",\"com\")"]
@@ -597,6 +604,8 @@ subdomain_label_neighbors s =
 --
 --   ==== _Examples_
 --
+--   >>> import Text.Parsec ( parse )
+--
 --   >>> let (Right r) = parse subdomain "" "www.example.com"
 --   >>> subdomain_has_equal_neighbors r
 --   False
@@ -641,7 +650,7 @@ instance Pretty Domain where
 --
 --   ==== _Examples_
 --
---   >>> import Text.Parsec ( parseTest )
+--   >>> import Text.Parsec ( parse, parseTest )
 --
 --   Make sure we can parse a single character:
 --
@@ -699,7 +708,7 @@ domain = try parse_subdomain <|> parse_empty
     parse_subdomain :: Parser Domain
     parse_subdomain = do
       s <- subdomain
-      if (length $ pretty_show s) <= 255
+      if length (pretty_show s) <= 255
       then return $ DomainName s
       else fail "subdomains can be at most 255 characters"
 
@@ -740,7 +749,7 @@ instance Pretty UserDomain where
 --
 --   ==== _Examples_
 --
---   >>> import Text.Parsec ( parseTest )
+--   >>> import Text.Parsec ( parse, parseTest )
 --
 --   We can really parse the root now!
 --
@@ -773,7 +782,7 @@ user_domain = try absolute <|> relative
     absolute :: Parser UserDomain
     absolute = do
       d <- domain
-      r <- char '.'
+      _ <- char '.'
       return $ UserDomainAbsolute d
 
     relative :: Parser UserDomain
index d6f7c8fdbf0d3656a49d09c59abc7c2886d0289f..52be5222b48096b14b596b195a82b17fc9efd4a4 100644 (file)
@@ -2,5 +2,4 @@ module Main
 where
 
 main :: IO ()
-main = do
-  putStrLn "Hello, world!"
+main = putStrLn "Hello, world!"
index 91158065ff717ddc71bc2b909c25ee422de49e7d..14911246c8cd801a7f38b16aaef7a672e4c30bba 100644 (file)
@@ -33,7 +33,7 @@ instance (Pretty a) => Pretty [a] where
 --   them too.
 --
 instance (Pretty a, Pretty b) => Pretty (a,b) where
-  pretty_show (x,y) = show (pretty_show x, pretty_show y)
+  pretty_show (x,y) = show (pretty_show x, pretty_show y)