Commit 6d3f28ae authored by Andrew Gibiansky's avatar Andrew Gibiansky

Reformatting code to match hindent

parent 831bf1be
{-# LANGUAGE NoImplicitPrelude #-}
-- | Description : mostly reversible conversion between ipynb and lhs
module IHaskell.Convert (convert) where
......
{-# LANGUAGE NoImplicitPrelude #-}
-- | Description: interpret flags parsed by "IHaskell.Flags"
module IHaskell.Convert.Args (ConvertSpec(..), fromJustConvertSpec, toConvertSpec) where
......
......@@ -71,10 +71,10 @@ cellToVal (Code i o) = object
] | _ <- take 1 o])
]
cellToVal (Markdown txt) = object
[ "cell_type" .= String "markdown"
, "metadata" .= object ["hidden" .= Bool False]
, "source" .= arrayFromTxt txt
]
[ "cell_type" .= String "markdown"
, "metadata" .= object ["hidden" .= Bool False]
, "source" .= arrayFromTxt txt
]
-- | arrayFromTxt makes a JSON array of string s
arrayFromTxt :: [LText] -> Value
......
......@@ -19,7 +19,7 @@ import Network.HTTP.Client
import Network.HTTP.Client.TLS
import Data.Aeson
import Data.String.Utils
import qualified Data.List as List
import qualified Data.List as List
import Data.Char (isAscii, isAlphaNum)
......@@ -55,8 +55,10 @@ instance FromJSON HoogleResponse where
query :: String -> IO (Either String String)
query str = do
request <- parseUrl $ queryUrl $ urlEncode str
catch (Right . CBS.unpack . LBS.toStrict . responseBody <$> withManager tlsManagerSettings (httpLbs request))
(\e -> return $ Left $ show (e :: SomeException))
catch
(Right . CBS.unpack . LBS.toStrict . responseBody <$> withManager tlsManagerSettings
(httpLbs request))
(\e -> return $ Left $ show (e :: SomeException))
where
queryUrl :: String -> String
......@@ -94,7 +96,7 @@ search string = do
case response of
Left err -> [NoResult err]
Right json ->
case eitherDecode $ LBS.fromStrict$ CBS.pack json of
case eitherDecode $ LBS.fromStrict $ CBS.pack json of
Left err -> [NoResult err]
Right results ->
case map SearchResult results of
......
{-# LANGUAGE NoImplicitPrelude #-}
-- | This module splits a shell command line into a list of strings,
-- one for each command / filename
module IHaskell.Eval.ParseShell (parseShell) where
......@@ -55,12 +56,12 @@ separator = many1 space <?> "separator"
-- | Input must terminate in a space character (like a \n)
shellWords :: Parser [String]
shellWords = try (eof *> return []) <|> do
x <- word
rest1 <- lookAhead (many anyToken)
ss <- separator
rest2 <- lookAhead (many anyToken)
xs <- shellWords
return $ x : xs
x <- word
rest1 <- lookAhead (many anyToken)
ss <- separator
rest2 <- lookAhead (many anyToken)
xs <- shellWords
return $ x : xs
parseShell :: String -> Either ParseError [String]
parseShell string = parse shellWords "shell" (string ++ "\n")
......@@ -116,6 +116,7 @@ pprDynFlags show_all dflags =
fstr, fnostr :: String -> O.SDoc
fstr str = O.text "-f" O.<> O.text str
fnostr str = O.text "-fno-" O.<> O.text str
(ghciFlags, others) = partition (\f -> flagSpecFlag f `elem` flgs) DynFlags.fFlags
......@@ -137,14 +138,16 @@ pprLanguages :: Bool -- ^ Whether to include flags which are on by default
-> O.SDoc
pprLanguages show_all dflags =
O.vcat
[O.text "base language is: " O.<>
case language dflags of
Nothing -> O.text "Haskell2010"
Just Haskell98 -> O.text "Haskell98"
Just Haskell2010 -> O.text "Haskell2010", (if show_all
then O.text "all active language options:"
else O.text "with the following modifiers:") O.$$
O.nest 2 (O.vcat (map (setting xopt) DynFlags.xFlags))]
[ O.text "base language is: " O.<>
case language dflags of
Nothing -> O.text "Haskell2010"
Just Haskell98 -> O.text "Haskell98"
Just Haskell2010 -> O.text "Haskell2010"
, (if show_all
then O.text "all active language options:"
else O.text "with the following modifiers:") O.$$
O.nest 2 (O.vcat (map (setting xopt) DynFlags.xFlags))
]
where
setting test flag
| quiet = O.empty
......
......@@ -252,7 +252,9 @@ replyTo interface req@ExecuteRequest { getCode = code } replyHeader state = do
convertSvgToHtml x = x
makeSvgImg :: Base64 -> String
makeSvgImg base64data = T.unpack $ "<img src=\"data:image/svg+xml;base64," <> base64data <> "\"/>"
makeSvgImg base64data = T.unpack $ "<img src=\"data:image/svg+xml;base64," <>
base64data <>
"\"/>"
prependCss (DisplayData MimeHtml html) =
DisplayData MimeHtml $ mconcat ["<style>", T.pack ihaskellCSS, "</style>", html]
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment