{-# LINE 1 "src/Quaalude.cpphs" #-}
# 1 "src/Quaalude.cpphs"
# 1 "<built-in>"
# 1 "<command-line>"
# 12 "<command-line>"
# 1 "/usr/include/stdc-predef.h" 1 3 4

# 17 "/usr/include/stdc-predef.h" 3 4










































# 12 "<command-line>" 2
# 1 "./dist/build/autogen/cabal_macros.h" 1



# 13 "./dist/build/autogen/cabal_macros.h"


# 24 "./dist/build/autogen/cabal_macros.h"


# 35 "./dist/build/autogen/cabal_macros.h"


# 46 "./dist/build/autogen/cabal_macros.h"


# 57 "./dist/build/autogen/cabal_macros.h"


# 68 "./dist/build/autogen/cabal_macros.h"


# 79 "./dist/build/autogen/cabal_macros.h"


# 90 "./dist/build/autogen/cabal_macros.h"


# 101 "./dist/build/autogen/cabal_macros.h"


# 112 "./dist/build/autogen/cabal_macros.h"


# 123 "./dist/build/autogen/cabal_macros.h"


# 134 "./dist/build/autogen/cabal_macros.h"


# 145 "./dist/build/autogen/cabal_macros.h"


# 156 "./dist/build/autogen/cabal_macros.h"


# 167 "./dist/build/autogen/cabal_macros.h"


# 178 "./dist/build/autogen/cabal_macros.h"


# 189 "./dist/build/autogen/cabal_macros.h"


# 200 "./dist/build/autogen/cabal_macros.h"


# 211 "./dist/build/autogen/cabal_macros.h"


# 222 "./dist/build/autogen/cabal_macros.h"


# 233 "./dist/build/autogen/cabal_macros.h"


# 244 "./dist/build/autogen/cabal_macros.h"


# 255 "./dist/build/autogen/cabal_macros.h"


# 266 "./dist/build/autogen/cabal_macros.h"


# 277 "./dist/build/autogen/cabal_macros.h"


# 288 "./dist/build/autogen/cabal_macros.h"


# 299 "./dist/build/autogen/cabal_macros.h"


# 310 "./dist/build/autogen/cabal_macros.h"


# 321 "./dist/build/autogen/cabal_macros.h"


# 332 "./dist/build/autogen/cabal_macros.h"


# 343 "./dist/build/autogen/cabal_macros.h"


# 354 "./dist/build/autogen/cabal_macros.h"


# 365 "./dist/build/autogen/cabal_macros.h"


# 376 "./dist/build/autogen/cabal_macros.h"


# 387 "./dist/build/autogen/cabal_macros.h"


# 398 "./dist/build/autogen/cabal_macros.h"


# 409 "./dist/build/autogen/cabal_macros.h"


# 420 "./dist/build/autogen/cabal_macros.h"


# 431 "./dist/build/autogen/cabal_macros.h"


# 442 "./dist/build/autogen/cabal_macros.h"


# 453 "./dist/build/autogen/cabal_macros.h"


# 464 "./dist/build/autogen/cabal_macros.h"


# 475 "./dist/build/autogen/cabal_macros.h"


# 486 "./dist/build/autogen/cabal_macros.h"


# 497 "./dist/build/autogen/cabal_macros.h"

# 12 "<command-line>" 2
# 1 "/usr/local/haskell/ghc-8.2.2-x86_64/lib/ghc-8.2.2/include/ghcversion.h" 1















# 12 "<command-line>" 2
# 1 "/tmp/ghc11676_0/ghc_2.h" 1


















































































































































































































































































































































































































# 12 "<command-line>" 2
# 1 "src/Quaalude.cpphs"
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Quaalude ( hex
                , bool
                , intersperse
                , transpose
                , sortBy
                , void
                , unless
                , when
                , join
                , fold
                , zipWithM_
                , zipWithM
                , filterM
                , encode
                , decode
                , fromMaybe
                , isPrefixOf
                , isSuffixOf
                , on
                , both
                , (***)
                , (&&&)
                , (<=<)
                , (<>)
                , first
                , second
                , getEnv
                , exitWith
                , showVersion
                , ExitCode (ExitSuccess)
                , MonadIO (..)
                -- * "System.Process.Ext" reëxports
                , silentCreateProcess
                -- * "Data.Text.Lazy" reëxports
                , Text
                , pack
                , unpack
                -- * "Control.Composition" reëxports
                , biaxe
                , (.*)
                , (.**)
                , thread
                -- * Dhall reëxports
                , Interpret
                , Inject
                , Generic
                , Binary
                , input
                , auto
                , detailed
                -- * Shake reëxports
                , Rules
                , Action
                , command
                , command_
                , (%>)
                , need
                , want
                , shake
                , Rebuild (..)
                , (~>)
                , cmd
                , cmd_
                , ShakeOptions (..)
                , shakeOptions
                , copyFile'
                , Change (..)
                , Verbosity (..)
                , removeFilesAfter
                , Lint (..)
                , takeBaseName
                , takeFileName
                , takeDirectory
                , (-<.>)
                -- * "System.Posix" reëxports
                , setFileMode
                , ownerModes
                -- * "Network.HTTP.Client.TLS" reëxports
                , tlsManagerSettings
                -- "Network.HTTP.Client" reëxports
                , newManager
                , parseRequest
                , httpLbs
                , Response (..)
                , Request (method, redirectCount)
                -- * ByteString reëxports
                , ByteString
                -- * Helpers for pretty-printing
                , (<#>)
                -- * "Text.PrettyPrint.ANSI.Leijen" reëxports
                , (<+>)
                , text
                , punctuate
                , dullred
                , linebreak
                , dullyellow
                , hardline
                , hang
                , indent
                , putDoc
                , Pretty (pretty)
                , module X
                -- Lens exports
                , over
                , _Just
                , view
                , _1
                , _2
                , _4
                , makeLensesFor
                , makeLenses
                , each
                , (&)
                , (%~)
                ) where

import           Control.Arrow                hiding ((<+>))
import           Control.Composition
import           Control.Monad
import           Control.Monad.IO.Class
import           Data.Binary
import           Data.Bool                    (bool)
import           Data.ByteString.Lazy         (ByteString)
import           Data.Foldable                (fold)
import           Data.List
import           Data.Maybe                   (fromMaybe)
import           Data.Semigroup
import           Data.Text.Lazy               (pack, unpack)
import           Data.Version                 (showVersion)
import           Development.Shake            hiding (getEnv)
import           Development.Shake.FilePath
import           Dhall                        hiding (bool)
import           Lens.Micro                   hiding (both)
import           Lens.Micro.Extras
import           Lens.Micro.TH
import           Network.HTTP.Client
import           Network.HTTP.Client.TLS      (tlsManagerSettings)
import           Numeric                      (showHex)
import           System.Directory             as X
import           System.Environment           (getEnv)
import           System.Exit                  (ExitCode (ExitSuccess), exitWith)

import           System.Posix.Files

import           System.Process               as X
import           System.Process.Ext
import           Text.PrettyPrint.ANSI.Leijen hiding (bool, (<$>), (<>))

infixr 5 <#>







hex :: Int -> String
hex = flip showHex mempty

instance Semigroup a => Semigroup (Action a) where
    (<>) a b = (<>) <$> a <*> b

instance (Semigroup a, Monoid a) => Monoid (Action a) where
    mempty = pure mempty
    mappend = (<>)

-- | Same as "Text.PrettyPrint.ANSI.Leijen"'s @<$>@, but doesn't clash with the
-- prelude.
(<#>) :: Doc -> Doc -> Doc
(<#>) a b = a <> line <> b