{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Hhp.Types where

import Control.Monad.Catch (catch)
import GHC (Ghc)

import Control.Applicative (Alternative (..))
import Control.Exception (IOException)
import Data.List (intercalate)

-- | Output style.
data OutputStyle
    = -- | S expression style.
      LispStyle
    | -- | Plain textstyle.
      PlainStyle

-- | The type for line separator. Historically, a Null string is used.
newtype LineSeparator = LineSeparator String

data Options = Options
    { Options -> OutputStyle
outputStyle :: OutputStyle
    , Options -> [String]
hlintOpts :: [String]
    , Options -> [String]
ghcOpts :: [GHCOption]
    , Options -> Bool
operators :: Bool
    -- ^ If 'True', 'browse' also returns operators.
    , Options -> Bool
detailed :: Bool
    -- ^ If 'True', 'browse' also returns types.
    , Options -> Bool
qualified :: Bool
    -- ^ If 'True', 'browse' will return fully qualified name
    , Options -> LineSeparator
lineSeparator :: LineSeparator
    -- ^ Line separator string.
    }

-- | A default 'Options'.
defaultOptions :: Options
defaultOptions :: Options
defaultOptions =
    Options
        { outputStyle :: OutputStyle
outputStyle = OutputStyle
PlainStyle
        , hlintOpts :: [String]
hlintOpts = []
        , ghcOpts :: [String]
ghcOpts = []
        , operators :: Bool
operators = Bool
False
        , detailed :: Bool
detailed = Bool
False
        , qualified :: Bool
qualified = Bool
False
        , lineSeparator :: LineSeparator
lineSeparator = String -> LineSeparator
LineSeparator String
"\0"
        }

----------------------------------------------------------------

type Builder = String -> String

-- |
--
-- >>> replace '"' "\\\"" "foo\"bar" ""
-- "foo\\\"bar"
replace :: Char -> String -> String -> Builder
replace :: Char -> String -> String -> Builder
replace Char
_ String
_ [] = Builder
forall a. a -> a
id
replace Char
c String
cs (Char
x : String
xs)
    | Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c = (String
cs String -> Builder
forall a. [a] -> [a] -> [a]
++) Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String -> String -> Builder
replace Char
c String
cs String
xs
    | Bool
otherwise = (Char
x Char -> Builder
forall a. a -> [a] -> [a]
:) Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String -> String -> Builder
replace Char
c String
cs String
xs

inter :: Char -> [Builder] -> Builder
inter :: Char -> [Builder] -> Builder
inter Char
_ [] = Builder
forall a. a -> a
id
inter Char
c [Builder]
bs = (Builder -> Builder -> Builder) -> [Builder] -> Builder
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 (\Builder
x Builder
y -> Builder
x Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
c Char -> Builder
forall a. a -> [a] -> [a]
:) Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder
y) [Builder]
bs

convert :: ToString a => Options -> a -> String
convert :: forall a. ToString a => Options -> a -> String
convert opt :: Options
opt@Options{outputStyle :: Options -> OutputStyle
outputStyle = OutputStyle
LispStyle} a
x = Options -> a -> Builder
forall a. ToString a => Options -> a -> Builder
toLisp Options
opt a
x String
"\n"
convert opt :: Options
opt@Options{outputStyle :: Options -> OutputStyle
outputStyle = OutputStyle
PlainStyle} a
x
    | String
str String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"\n" = String
""
    | Bool
otherwise = String
str
  where
    str :: String
str = Options -> a -> Builder
forall a. ToString a => Options -> a -> Builder
toPlain Options
opt a
x String
"\n"

class ToString a where
    toLisp :: Options -> a -> Builder
    toPlain :: Options -> a -> Builder

lineSep :: Options -> String
lineSep :: Options -> String
lineSep Options
opt = String
lsep
  where
    LineSeparator String
lsep = Options -> LineSeparator
lineSeparator Options
opt

-- |
--
-- >>> toLisp defaultOptions "fo\"o" ""
-- "\"fo\\\"o\""
-- >>> toPlain defaultOptions "foo" ""
-- "foo"
instance ToString String where
    toLisp :: Options -> String -> Builder
toLisp Options
opt = Options -> String -> Builder
quote Options
opt
    toPlain :: Options -> String -> Builder
toPlain Options
opt = Char -> String -> String -> Builder
replace Char
'\n' (Options -> String
lineSep Options
opt)

-- |
--
-- >>> toLisp defaultOptions ["foo", "bar", "ba\"z"] ""
-- "(\"foo\" \"bar\" \"ba\\\"z\")"
-- >>> toPlain defaultOptions ["foo", "bar", "baz"] ""
-- "foo\nbar\nbaz"
instance ToString [String] where
    toLisp :: Options -> [String] -> Builder
toLisp Options
opt = Options -> [String] -> Builder
toSexp1 Options
opt
    toPlain :: Options -> [String] -> Builder
toPlain Options
opt = Char -> [Builder] -> Builder
inter Char
'\n' ([Builder] -> Builder)
-> ([String] -> [Builder]) -> [String] -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Builder) -> [String] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map (Options -> String -> Builder
forall a. ToString a => Options -> a -> Builder
toPlain Options
opt)

-- |
--
-- >>> let inp = [((1,2,3,4),"foo"),((5,6,7,8),"bar")] :: [((Int,Int,Int,Int),String)]
-- >>> toLisp defaultOptions inp ""
-- "((1 2 3 4 \"foo\") (5 6 7 8 \"bar\"))"
-- >>> toPlain defaultOptions inp ""
-- "1 2 3 4 \"foo\"\n5 6 7 8 \"bar\""
instance ToString [((Int, Int, Int, Int), String)] where
    toLisp :: Options -> [((Int, Int, Int, Int), String)] -> Builder
toLisp Options
opt = [Builder] -> Builder
toSexp2 ([Builder] -> Builder)
-> ([((Int, Int, Int, Int), String)] -> [Builder])
-> [((Int, Int, Int, Int), String)]
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((Int, Int, Int, Int), String) -> Builder)
-> [((Int, Int, Int, Int), String)] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map ((Int, Int, Int, Int), String) -> Builder
toS
      where
        toS :: ((Int, Int, Int, Int), String) -> Builder
toS ((Int, Int, Int, Int), String)
x = (Char
'(' Char -> Builder
forall a. a -> [a] -> [a]
:) Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> ((Int, Int, Int, Int), String) -> Builder
tupToString Options
opt ((Int, Int, Int, Int), String)
x Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
')' Char -> Builder
forall a. a -> [a] -> [a]
:)
    toPlain :: Options -> [((Int, Int, Int, Int), String)] -> Builder
toPlain Options
opt = Char -> [Builder] -> Builder
inter Char
'\n' ([Builder] -> Builder)
-> ([((Int, Int, Int, Int), String)] -> [Builder])
-> [((Int, Int, Int, Int), String)]
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((Int, Int, Int, Int), String) -> Builder)
-> [((Int, Int, Int, Int), String)] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map (Options -> ((Int, Int, Int, Int), String) -> Builder
tupToString Options
opt)

toSexp1 :: Options -> [String] -> Builder
toSexp1 :: Options -> [String] -> Builder
toSexp1 Options
opt [String]
ss = (Char
'(' Char -> Builder
forall a. a -> [a] -> [a]
:) Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> [Builder] -> Builder
inter Char
' ' ((String -> Builder) -> [String] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map (Options -> String -> Builder
quote Options
opt) [String]
ss) Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
')' Char -> Builder
forall a. a -> [a] -> [a]
:)

toSexp2 :: [Builder] -> Builder
toSexp2 :: [Builder] -> Builder
toSexp2 [Builder]
ss = (Char
'(' Char -> Builder
forall a. a -> [a] -> [a]
:) Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> [Builder] -> Builder
inter Char
' ' [Builder]
ss Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
')' Char -> Builder
forall a. a -> [a] -> [a]
:)

tupToString :: Options -> ((Int, Int, Int, Int), String) -> Builder
tupToString :: Options -> ((Int, Int, Int, Int), String) -> Builder
tupToString Options
opt ((Int
a, Int
b, Int
c, Int
d), String
s) =
    (Int -> String
forall a. Show a => a -> String
show Int
a String -> Builder
forall a. [a] -> [a] -> [a]
++)
        Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
' ' Char -> Builder
forall a. a -> [a] -> [a]
:)
        Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> String
forall a. Show a => a -> String
show Int
b String -> Builder
forall a. [a] -> [a] -> [a]
++)
        Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
' ' Char -> Builder
forall a. a -> [a] -> [a]
:)
        Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> String
forall a. Show a => a -> String
show Int
c String -> Builder
forall a. [a] -> [a] -> [a]
++)
        Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
' ' Char -> Builder
forall a. a -> [a] -> [a]
:)
        Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> String
forall a. Show a => a -> String
show Int
d String -> Builder
forall a. [a] -> [a] -> [a]
++)
        Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
' ' Char -> Builder
forall a. a -> [a] -> [a]
:)
        Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> String -> Builder
quote Options
opt String
s -- fixme: quote is not necessary

quote :: Options -> String -> Builder
quote :: Options -> String -> Builder
quote Options
opt String
str = (String
"\"" String -> Builder
forall a. [a] -> [a] -> [a]
++) Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Builder
quote' String
str String -> Builder
forall a. [a] -> [a] -> [a]
++) Builder -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"\"" String -> Builder
forall a. [a] -> [a] -> [a]
++)
  where
    lsep :: String
lsep = Options -> String
lineSep Options
opt
    quote' :: Builder
quote' [] = []
    quote' (Char
x : String
xs)
        | Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n' = String
lsep String -> Builder
forall a. [a] -> [a] -> [a]
++ Builder
quote' String
xs
        | Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\\' = String
"\\\\" String -> Builder
forall a. [a] -> [a] -> [a]
++ Builder
quote' String
xs
        | Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'"' = String
"\\\"" String -> Builder
forall a. [a] -> [a] -> [a]
++ Builder
quote' String
xs
        | Bool
otherwise = Char
x Char -> Builder
forall a. a -> [a] -> [a]
: Builder
quote' String
xs

----------------------------------------------------------------

-- | The environment where this library is used.
data Cradle = Cradle
    { Cradle -> String
cradleCurrentDir :: FilePath
    -- ^ The directory where this library is executed.
    , Cradle -> String
cradleRootDir :: FilePath
    -- ^ The project root directory.
    , Cradle -> Maybe String
cradleCabalFile :: Maybe FilePath
    -- ^ The file name of the found cabal file.
    , Cradle -> [GhcPkgDb]
cradlePkgDbStack :: [GhcPkgDb]
    -- ^ Package database stack
    }
    deriving (Cradle -> Cradle -> Bool
(Cradle -> Cradle -> Bool)
-> (Cradle -> Cradle -> Bool) -> Eq Cradle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Cradle -> Cradle -> Bool
== :: Cradle -> Cradle -> Bool
$c/= :: Cradle -> Cradle -> Bool
/= :: Cradle -> Cradle -> Bool
Eq, Int -> Cradle -> Builder
[Cradle] -> Builder
Cradle -> String
(Int -> Cradle -> Builder)
-> (Cradle -> String) -> ([Cradle] -> Builder) -> Show Cradle
forall a.
(Int -> a -> Builder)
-> (a -> String) -> ([a] -> Builder) -> Show a
$cshowsPrec :: Int -> Cradle -> Builder
showsPrec :: Int -> Cradle -> Builder
$cshow :: Cradle -> String
show :: Cradle -> String
$cshowList :: [Cradle] -> Builder
showList :: [Cradle] -> Builder
Show)

----------------------------------------------------------------

-- | GHC package database flags.
data GhcPkgDb = GlobalDb | UserDb | PackageDb String deriving (GhcPkgDb -> GhcPkgDb -> Bool
(GhcPkgDb -> GhcPkgDb -> Bool)
-> (GhcPkgDb -> GhcPkgDb -> Bool) -> Eq GhcPkgDb
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GhcPkgDb -> GhcPkgDb -> Bool
== :: GhcPkgDb -> GhcPkgDb -> Bool
$c/= :: GhcPkgDb -> GhcPkgDb -> Bool
/= :: GhcPkgDb -> GhcPkgDb -> Bool
Eq, Int -> GhcPkgDb -> Builder
[GhcPkgDb] -> Builder
GhcPkgDb -> String
(Int -> GhcPkgDb -> Builder)
-> (GhcPkgDb -> String) -> ([GhcPkgDb] -> Builder) -> Show GhcPkgDb
forall a.
(Int -> a -> Builder)
-> (a -> String) -> ([a] -> Builder) -> Show a
$cshowsPrec :: Int -> GhcPkgDb -> Builder
showsPrec :: Int -> GhcPkgDb -> Builder
$cshow :: GhcPkgDb -> String
show :: GhcPkgDb -> String
$cshowList :: [GhcPkgDb] -> Builder
showList :: [GhcPkgDb] -> Builder
Show)

-- | A single GHC command line option.
type GHCOption = String

-- | An include directory for modules.
type IncludeDir = FilePath

-- | A package name.
type PackageBaseName = String

-- | A package version.
type PackageVersion = String

-- | A package id.
type PackageId = String

-- | A package's name, verson and id.
type Package = (PackageBaseName, PackageVersion, PackageId)

pkgName :: Package -> PackageBaseName
pkgName :: Package -> String
pkgName (String
n, String
_, String
_) = String
n

pkgVer :: Package -> PackageVersion
pkgVer :: Package -> String
pkgVer (String
_, String
v, String
_) = String
v

pkgId :: Package -> PackageId
pkgId :: Package -> String
pkgId (String
_, String
_, String
i) = String
i

showPkg :: Package -> String
showPkg :: Package -> String
showPkg (String
n, String
v, String
_) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"-" [String
n, String
v]

showPkgId :: Package -> String
showPkgId :: Package -> String
showPkgId (String
n, String
v, String
"") = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"-" [String
n, String
v]
showPkgId (String
n, String
v, String
i) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"-" [String
n, String
v, String
i]

-- | Haskell expression.
type Expression = String

-- | Module name.
type ModuleString = String

-- | Option information for GHC
data CompilerOptions = CompilerOptions
    { CompilerOptions -> [String]
ghcOptions :: [GHCOption]
    -- ^ Command line options
    , CompilerOptions -> [String]
includeDirs :: [IncludeDir]
    -- ^ Include directories for modules
    , CompilerOptions -> [Package]
depPackages :: [Package]
    -- ^ Dependent package names
    }
    deriving (CompilerOptions -> CompilerOptions -> Bool
(CompilerOptions -> CompilerOptions -> Bool)
-> (CompilerOptions -> CompilerOptions -> Bool)
-> Eq CompilerOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompilerOptions -> CompilerOptions -> Bool
== :: CompilerOptions -> CompilerOptions -> Bool
$c/= :: CompilerOptions -> CompilerOptions -> Bool
/= :: CompilerOptions -> CompilerOptions -> Bool
Eq, Int -> CompilerOptions -> Builder
[CompilerOptions] -> Builder
CompilerOptions -> String
(Int -> CompilerOptions -> Builder)
-> (CompilerOptions -> String)
-> ([CompilerOptions] -> Builder)
-> Show CompilerOptions
forall a.
(Int -> a -> Builder)
-> (a -> String) -> ([a] -> Builder) -> Show a
$cshowsPrec :: Int -> CompilerOptions -> Builder
showsPrec :: Int -> CompilerOptions -> Builder
$cshow :: CompilerOptions -> String
show :: CompilerOptions -> String
$cshowList :: [CompilerOptions] -> Builder
showList :: [CompilerOptions] -> Builder
Show)

instance Alternative Ghc where
    Ghc a
x <|> :: forall a. Ghc a -> Ghc a -> Ghc a
<|> Ghc a
y = Ghc a
x Ghc a -> (IOException -> Ghc a) -> Ghc a
forall e a.
(HasCallStack, Exception e) =>
Ghc a -> (e -> Ghc a) -> Ghc a
forall (m :: * -> *) e a.
(MonadCatch m, HasCallStack, Exception e) =>
m a -> (e -> m a) -> m a
`catch` (\(IOException
_ :: IOException) -> Ghc a
y)
    empty :: forall a. Ghc a
empty = Ghc a
forall a. HasCallStack => a
undefined

unsafeHead :: [a] -> a
unsafeHead :: forall a. [a] -> a
unsafeHead [] = String -> a
forall a. HasCallStack => String -> a
error String
"unsafeHead"
unsafeHead (a
x : [a]
_) = a
x