cfenv-0.1.0.0: A library getting the environment when running on Cloud Foundry

Safe HaskellNone
LanguageHaskell2010

System.CloudFoundry.Environment

Description

The purpose of this library is to assist you in writing Haskell apps that run on Cloud Foundry. It provides convenience functions and structures that map to Cloud Foundry environment variable primitives.

This package is a port of https://github.com/cloudfoundry-community/go-cfenv

Synopsis

Documentation

current :: IO Application Source #

Get the current Cloud Foundry environment.

Example using scotty:

import Data.String (fromString)
import Data.Monoid (mconcat)

import Web.Scotty

import qualified System.CloudFoundry.Environment as CfEnv

main = do
  app <- CfEnv.current

  scotty (CfEnv.port app) $
    get "/" $ do
      html $ mconcat ["<pre>", (fromString (show app)), "</pre>"]

isRunningOnCf :: IO Bool Source #

Detect if the application is running as a Cloud Foundry application.

import System.CloudFoundry.Environment CfEnv

main :: IO ()
main = do
    isRunningOnCf <- CfEnv.isRunningOnCf

    if isRunningOnCf
        then putStrLn "Running on Cloud Foundry"
        else putStrLn "Not running on Cloud Foundry"

lookupCurrent :: IO (Maybe Application) Source #

Get the current Cloud Foundry environment and return the result in a Maybe. See current.

credentialString Source #

Arguments

:: String

The key to each for in the credentials section

-> Service

The service to get the value from

-> Maybe String

The value of that credential string if it is found

Get a credential string from a service.

withLabel Source #

Arguments

:: String

The label to search for

-> Services

All services bound to the application

-> [Service]

A list of matching services

Get the services by label.

withName Source #

Arguments

:: String

The name of the service to be found

-> Services

All services bound to the application

-> Maybe Service

The service if it is found

Get the service by name.

withTag Source #

Arguments

:: String

The tag to search for

-> Services

All services bound to the application

-> [Service]

A list of matching services

Get all services which have the provided tag.

data Application Source #

Holds information about the current app running on Cloud Foundry. This is returned from current.

Constructors

Application 

Fields

data Limits Source #

Constructors

Limits 

Fields

Instances

Eq Limits Source # 

Methods

(==) :: Limits -> Limits -> Bool #

(/=) :: Limits -> Limits -> Bool #

Show Limits Source # 
Generic Limits Source # 

Associated Types

type Rep Limits :: * -> * #

Methods

from :: Limits -> Rep Limits x #

to :: Rep Limits x -> Limits #

FromJSON Limits Source # 
type Rep Limits Source # 
type Rep Limits = D1 * (MetaData "Limits" "System.CloudFoundry.Environment.Internal.Types" "cfenv-0.1.0.0-J5pip5JUPwB2saLZYKBhuP" False) (C1 * (MetaCons "Limits" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "disk") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "fds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "mem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))))

data Service Source #

Description of a bound service. Use credentialString to extract the connection details.

Constructors

Service 

newtype Services Source #

A collection of Service instances. withTag, withName and withLabel can be used to find the specific services that you want.

Constructors

Services (Map String [Service]) 

data CfEnvError Source #

Exceptions which are raised from this package.

Constructors

DecodeError String String

Thrown when a JSON decode failed for either the VCAP_APPLICATION or VCAP_SERIVCES environment variables.

NotInteger String String

Thrown when an environment variable which is meant to contain an integer contains invalid characters.