Code Monkey home page Code Monkey logo

envy's Introduction

envy

Hackage Hackage Dependencies Haskell Programming Language BSD3 License Build Status

Let's face it, dealing with environment variables in Haskell isn't that satisfying.

import System.Environment
import Data.Text (pack)
import Text.Read (readMaybe)

data ConnectInfo = ConnectInfo {
  pgPort :: Int
  pgURL  :: Text
} deriving (Show, Eq)

getPGPort :: IO ConnectInfo
getPGPort = do
  portResult <- lookupEnv "PG_PORT"
  urlResult  <- lookupEnv "PG_URL"
  case (portResult, urlResult) of
    (Just port, Just url) ->
      case readMaybe port :: Maybe Int of
	Nothing -> error "PG_PORT isn't a number"
	Just portNum -> return $ ConnectInfo portNum (pack url)
    (Nothing, _) -> error "Couldn't find PG_PORT"
    (_, Nothing) -> error "Couldn't find PG_URL"
    -- Pretty gross right...

Another attempt to remedy the lookup madness is with a MaybeT IO a. See below.

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Control.Applicative
import Control.Monad.Trans.Maybe
import Control.Monad.IO.Class
import System.Environment

newtype Env a = Env { unEnv :: MaybeT IO a }
    deriving (Functor, Applicative, Monad, MonadIO, Alternative, MonadPlus)

getEnv :: Env a -> IO (Maybe a)
getEnv env = runMaybeT (unEnv env)

env :: String -> Env a
env key = Env (MaybeT (lookupEnv key))

connectInfo :: Env ConnectInfo
connectInfo = ConnectInfo
   <$> env "PG_HOST"
   <*> env "PG_PORT"
   <*> env "PG_USER"
   <*> env "PG_PASS"
   <*> env "PG_DB"

This abstraction falls short in two areas:

  • Lookups don't return any information when a variable doesn't exist (just a Nothing)
  • Lookups don't attempt to parse the returned type into something meaningful (everything is returned as a String because lookupEnv :: String -> IO (Maybe String))

What if we could apply aeson's FromJSON / ToJSON pattern to give us variable lookups that provide both key-lookup and parse failure information? Armed with the GeneralizedNewTypeDeriving extension we can derive instances of Var that will parse to and from an environment variable. The Var typeclass is simply:

class Var a where
  toVar   :: a -> String
  fromVar :: String -> Maybe a

With instances for most concrete and primitive types supported (Word8 - Word64, Int, Integer, String, Text, etc.) the Var class is easily deriveable. The FromEnv typeclass provides a parser type that is an instance of MonadError String and MonadIO. This allows for connection pool initialization inside of our environment parser and custom error handling. The ToEnv class allows us to create an environment configuration given any a. See below for an example.

{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE DeriveDataTypeable         #-}
------------------------------------------------------------------------------
module Main ( main ) where
------------------------------------------------------------------------------
import           Control.Applicative
import           Control.Exception
import           Control.Monad
import           Data.Either
import           Data.Word
import           System.Environment
import           System.Envy
------------------------------------------------------------------------------
data ConnectInfo = ConnectInfo {
      pgHost :: String
    , pgPort :: Word16
    , pgUser :: String
    , pgPass :: String
    , pgDB   :: String
  } deriving (Show)

------------------------------------------------------------------------------
-- | FromEnv instances support popular aeson combinators *and* IO
-- for dealing with connection pool initialization. `env` is equivalent to (.:) in `aeson`
-- and `envMaybe` is equivalent to (.:?), except here the lookups are impure.
instance FromEnv ConnectInfo where
  fromEnv _ =
    ConnectInfo <$> envMaybe "PG_HOST" .!= "localhost"
		<*> env "PG_PORT"
		<*> env "PG_USER"
		<*> env "PG_PASS"
		<*> env "PG_DB"

------------------------------------------------------------------------------
-- | To Environment Instances
-- (.=) is a smart constructor for producing types of `EnvVar` (which ensures
-- that Strings are set properly in an environment so they can be parsed properly
instance ToEnv ConnectInfo where
  toEnv ConnectInfo {..} = makeEnv
       [ "PG_HOST" .= pgHost
       , "PG_PORT" .= pgPort
       , "PG_USER" .= pgUser
       , "PG_PASS" .= pgPass
       , "PG_DB"   .= pgDB
       ]

------------------------------------------------------------------------------
-- | Example
main :: IO ()
main = do
   setEnvironment (toEnv :: EnvList ConnectInfo)
   print =<< do decodeEnv :: IO (Either String ConnectInfo)
   -- unsetEnvironment (toEnv :: EnvList ConnectInfo)  -- remove when done

Our parser might also make use a set of an optional default values provided by the user, for dealing with errors when reading from the environment

instance FromEnv ConnectInfo where
  fromEnv Nothing =
    ConnectInfo <$> envMaybe "PG_HOST" .!= "localhost"
		<*> env "PG_PORT"
		<*> env "PG_USER"
		<*> env "PG_PASS"
		<*> env "PG_DB"

  fromEnv (Just def) =
    ConnectInfo <$> envMaybe "PG_HOST" .!= (pgHost def)
		<*> envMaybe "PG_PORT" .!= (pgPort def)
		<*> env "PG_USER" .!= (pgUser def)
		<*> env "PG_PASS" .!= (pgPass def)
		<*> env "PG_DB" .!= (pgDB def)

Note: As of base 4.7 setEnv and getEnv throw an IOException if a = is present in an environment. envy catches these synchronous exceptions and delivers them purely to the end user.

Generics

As of version 1.0, all FromEnv instance boilerplate can be completely removed thanks to GHC.Generics! Below is an example.

{-# LANGUAGE DeriveGeneric #-}
module Main where

import System.Envy
import GHC.Generics
import System.Environment.Blank

-- This record corresponds to our environment, where the field names become the variable names, and the values the environment variable value
data PGConfig = PGConfig {
    pgHost :: String -- "PG_HOST"
  , pgPort :: Int    -- "PG_PORT"
  } deriving (Generic, Show)

instance FromEnv PGConfig
-- Generically creates instance for retrieving environment variables (PG_HOST, PG_PORT)

main :: IO ()
main = do
  _ <- setEnv "PG_HOST" "valueFromEnv" True
  _ <- setEnv "PG_PORT"  "66354651" True
  print =<< do decodeEnv :: IO (Either String PGConfig)
 -- > PGConfig { pgHost = "valueFromEnv", pgPort = 66354651 }

If the variables are not found in the environment, the parser will currently fail with an error about the first missing field.

The user can decide to provide a default value, whose fields will be used by the generic instance, if retrieving them from the environment fails.

defConfig :: PGConfig
defConfig = PGConfig "localhost" 5432

main :: IO ()
main = do
  _ <- setEnv "PG_HOST" "customURL" True
  print =<< decodeWithDefaults defConfig
 -- > PGConfig { pgHost = "customURL", pgPort = 5432 }

Suppose you'd like to customize the field name (i.e. add your own prefix, or drop the existing record prefix). This too is possible. See below.

{-# LANGUAGE DeriveGeneric #-}
module Main where

import System.Envy
import GHC.Generics

data PGConfig = PGConfig {
    connectHost :: String -- "PG_HOST"
  , connectPort :: Int    -- "PG_PORT"
  } deriving (Generic, Show)

instance DefConfig PGConfig where
  defConfig = PGConfig "localhost" 5432

-- All fields will be converted to uppercase
instance FromEnv PGConfig where
  fromEnv = gFromEnvCustom Option {
                    dropPrefixCount = 7
                  , customPrefix = "CUSTOM"
		  }

main :: IO ()
main =
  _ <- setEnv "CUSTOM_HOST" "customUrl" True
  print =<< do decodeEnv :: IO (Either String PGConfig)
 -- PGConfig { pgHost = "customUrl", pgPort = 5432 }

It's also possible to avoid typeclasses altogether using runEnv with gFromEnvCustom.

{-# LANGUAGE DeriveGeneric #-}
module Main where

import System.Envy
import GHC.Generics

data PGConfig = PGConfig {
    pgHost :: String -- "PG_HOST"
  , pgPort :: Int    -- "PG_PORT"
  } deriving (Generic, Show)

-- All fields will be converted to uppercase
getPGEnv :: IO (Either String PGConfig)
getPGEnv = runEnv $ gFromEnvCustom defOption
                                   (Just (PGConfig "localhost" 5432))

main :: IO ()
main = print =<< getPGEnv
 -- PGConfig { pgHost = "localhost", pgPort = 5432 }

envy's People

Contributors

bsima avatar contrun avatar dmjio avatar dzhus avatar iamfromspace avatar igrep avatar jkachmar avatar kyleondy avatar mookerji avatar nitinprakash96 avatar nlinker avatar puffnfresh avatar qwbarch avatar tfausak avatar timmytofu avatar ysangkok avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar

envy's Issues

Dont't make implementors of FromEnv instance think of the default value

As the author of #19 said, I prefer raising an error when Parser fails some way.
So types without default value is not bad.
Why does the FromEnv class force the instance to handle the default value?
If a default value is really necessary, just use fromLeft:

import Data.Either

print =<< (fromLeft defaultConfig <$> decodeEnv :: IO (Either String PGConfig))

Thinking of the default is not the responsibility of the instances of FromEnv.

What is the proper way of grouping env vars into product Haskell types?

Hi! I'd like to know what is the proper way to group multiple independent env vars prefixed with a component name into a Haskell component structure that represent the component as a whole? Basically I want these vars

DB_NAME=
DB_PORT=

to be mapped into a single data DbSettings ..., so that DbSettings itself can be used in larger env var parsers like:

data AppSettings = AppSettings
    { something :: Text
    , dbSettings :: DbSettings
    }

Normally, I'd first define an instance of Var a, but fromVar is only provided with a single variable, not a set of items. Does it mean that I should omit declaring instances for Var a and proceed with manual parsing inside instances of FromEnv a?

Error Compiling Example Program

Hi,

I tried to compile the example you provided verbatim.

{-# LANGUAGE DeriveGeneric #-}
module Main where

import System.Envy
import GHC.Generics

-- This record corresponds to our environment, where the field names become the variable names, and the values the environment variable value
data PGConfig = PGConfig {
    pgHost :: String -- "PG_HOST"
  , pgPort :: Int    -- "PG_PORT"
  } deriving (Generic, Show)

-- Default configuration will be used for fields that could not be retrieved from the environment
instance DefConfig PGConfig where
  defConfig = PGConfig "localhost" 5432

instance FromEnv PGConfig
-- Generically creates instance for retrieving environment variables (PG_HOST, PG_PORT)

main :: IO ()
main =
  print =<< decodeEnv :: IO (Either String PGConfig)
 -- > PGConfig { pgHost = "customURL", pgPort = 5432 }

I get the following error:

/Users/traviswhitton/Projects/haskell/jstats/app/Main.hs:22:3: error:
    • Couldn't match type ‘()’ with ‘Either String PGConfig’
      Expected type: IO (Either String PGConfig)
        Actual type: IO ()
    • In the expression:
          print =<< decodeEnv :: IO (Either String PGConfig)
      In an equation for ‘main’:
          main = print =<< decodeEnv :: IO (Either String PGConfig)
   |
22 |   print =<< decodeEnv :: IO (Either String PGConfig)
   |   ^^^^^^^^^^^^^^^^^^^

/Users/traviswhitton/Projects/haskell/jstats/app/Main.hs:22:3: error:
    • Couldn't match type ‘Either String PGConfig’ with ‘()’
      Expected type: IO ()
        Actual type: IO (Either String PGConfig)
    • In the expression:
          print =<< decodeEnv :: IO (Either String PGConfig)
      In an equation for ‘main’:
          main = print =<< decodeEnv :: IO (Either String PGConfig)
   |
22 |   print =<< decodeEnv :: IO (Either String PGConfig)
   |   ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

Am I doing something wrong? Thanks.

Constraints on base are incorrect for 2.0 and 2.1

Envy uses System.Environment.Blank, but this was not introduced until base-4.11. This means that when building with older versions of GHC and Cabal, the constraint solver will succeed and select 2.1 as compatible, but fail to build. It would be better if instead the constraint solver would instead select an older version (assuming it was compatible with the user's needs) or simply failed to solve at all, so that the user would know the next appropriate step.

I'll put up a pull request shortly, but this also needs a revision in Hackage to work correctly.

Generics without def config

If I have the following data type:

data MyEnv = MyEnv {
  envvar1 :: Text
  envvar2 :: Text
} deriving (Generic, FromEnv)

I am forced to write a DefConfig. However, I would prefer that if MyEnv can't be loaded from the environment, I just get an error message Failed to load ENVVAR1....

I've tried just setting an error in the DefConfig instance, but it always fails. I could make every field Maybe Text, but then I would have to handle the errors manually.

Am I missing something?

Indirect environment variables

We often use indirect env variables such as

DB_PROVIDER=LOCAL_DB_PROVIDER
LOCAL_DB_PROVIDER=postgres://.....

I am trying to read the env variable using something like

env <$> env "DB_PROVIDER"

but I can't quite get it to work. Any thoughts on this ?

Question: Semantics of `envMaybe`

envMaybe indicates that it will return Nothing if the environmental variable is not set, but it also returns Nothing if the environmental variable is set but is not parsable into the domain data type - i.e., fromVar returns Nothing.

You can construct a function with the the same type but different semantics, in that it will return Nothing if the variable is not set, but if the variable is set, it will attempt to parse it and error out if it cannot.

I am using such a function in my own project, and it looks like this (though I am sure there are more idiomatic ways to write this):

parseEnv :: Var a => String -> Parser (Maybe a)
parseEnv envName = do
  let parseError = throwError $ "Unable to parse " <> envName
  mStr <- optional (env envName) `catchError` (\_ -> pure Nothing)
  maybe (pure Nothing) (maybe parseError (pure . Just) . fromVar) mStr

Should something like this be added to the library, or is it easy enough to build with the current functions and I did more work than necessary?

Addendum

The haskell script below showcased the the following behavior:

  1. When "ENV_INT" is not found in the environment, it returns Nothing for the Int field of the Environment data type.
  2. When "ENV_INT" is found in the environment, but not parsable into an Int, then the parser fails.
  3. When "ENV_INT" is found in the environment, and parsable into an Int, then the parser succeeds with a Just.
#!/usr/bin/env stack
-- stack --resolver lts-14.7 script

{-# LANGUAGE DeriveGeneric       #-}
{-# LANGUAGE ScopedTypeVariables #-}

import           Control.Applicative
import           Control.Monad.Error.Class
import           GHC.Generics
import           System.Envy
import           Text.Read

newtype Custom = Custom { unCustom :: Int } deriving (Show, Eq)

instance Var Custom where
  toVar = toVar . unCustom
  fromVar s = Custom <$> readMaybe s


data Environment = Environment { envInt :: Maybe Int, envString :: Maybe String, envCustom :: Maybe Custom } deriving (Show, Eq, Generic)

instance FromEnv Environment where
  fromEnv _ = Environment <$> parseEnv "ENV_INT" <*> parseEnv "ENV_STRING" <*> parseEnv "ENV_CUSTOM"

parseEnv :: Var a => String -> Parser (Maybe a)
parseEnv envName = do
  let parseError = throwError $ "Unable to parse " <> envName
  mStr <- optional (env envName) `catchError` (\_ -> pure Nothing)
  maybe (pure Nothing) (maybe parseError (pure . Just) . fromVar) mStr

emptyEnv :: Environment
emptyEnv = Environment { envInt = Nothing, envString = Nothing, envCustom = Nothing}

main :: IO ()
main = do
  env <- decodeEnv :: IO (Either String Environment)
  print env

Poor error messages for bool variables

Parsing a bool variable, not only does "true" not work as a value, but the error message is not helpful in finding out that I should specify "True":

Parse failure: could not parse variable "TEST_BOOL" into type [Char]

Relax dependency on bytestring

The dependency on bytestring (<0.11) prevents the latest release to build with GHC 9.2.4. It appears that a simple adjustment of the dependency would be enough.

(Maybe this is something that could be made quickly by just revising on Hackage, I see @endgame has made such changes in the past.)

envy-2.0.0.0 and 2.1.0.0: metadata revisions published to Hackage

The released versions of envy-2.0.0.0 and envy-2.1.0.0 import System.Environment.Blank, a module that does not appear in base until base-4.11.0.0.

I see that master has been updated by #42 , so in my role as Hackage Trustee I have created metadata revisions for the affected versions on Hackage. This issue is just a notification per Trustee policy; no action is required.

provide a way to extract/print the names of environment variables used?

It'd be nice to be able to quickly produce a list of generated environment variable names being used, when one makes an instance of FromEnv for a type that has a Generics instance. That way, the list can be included in documentation.

The following code provides a method extract to do this:

class Extract a where
  extract :: a -> [String]
  default extract :: (GExtract (Rep a), Generic a) => a -> [String]
  extract x = gExtract (from x) defOption

class GExtract f where
  gExtract :: f a -> Option -> [String]

instance (GExtract a, GExtract b) => GExtract (a :*: b) where
  gExtract (a :*: b) opts = gExtract a opts <> gExtract b opts
instance GExtract a => GExtract (C1 i a) where
  gExtract (M1 x) = gExtract x
instance GExtract a => GExtract (D1 i a) where
  gExtract (M1 x) = gExtract x
instance (Selector s, Var a) => GExtract (S1 s (K1 i a)) where
  gExtract m@(M1 (K1 def)) opts = [toEnvName opts $ selName m]
where `selName` and `snake` are split out into top level functions to avoid duplication (expand for details).
toEnvName :: Option -> String -> String
toEnvName Option{..} xs =
  let name = snake (drop dropPrefixCount xs)
  in if customPrefix == mempty
       then name
       else map toUpper customPrefix ++ "_" ++ name

snake :: String -> String
snake = map toUpper . snakeCase
  where
      applyFirst :: (Char -> Char) -> String -> String
      applyFirst _ []     = []
      applyFirst f [x]    = [f x]
      applyFirst f (x:xs) = f x: xs

      snakeCase :: String -> String
      snakeCase = u . applyFirst toLower
        where u []                 = []
              u (x:xs) | isUpper x = '_' : toLower x : snakeCase xs
                       | otherwise = x : u xs

Is this a feature that could be added to Envy?

Allow using unit as an environment variable

TL;DR: Can Envy add a Var instance for ()?

I want to keep all of my application configuration in a single data type. Most of the config comes from the environment, but some of it comes from other sources. (The stuff that comes from other sources is more like state than config, but it makes sense to me to keep it all together.) For example, I might read a Port from the environment but also have a Manager in the config.

Obviously the manager can't come from the environment. I wanted to express this in the type system, so I tried something like this:

data Config manager = Config { port :: Port, manager :: manager }
  deriving Generic

type ConfigWithoutManager = Config () -- or Void

type ConfigWithManager = Config Manager

instance DefConfig ConfigWithoutManager where
  defConfig = Config { port = 8080, manager = () }

instance FromEnv ConfigWithoutManager

With that setup I figured I could decodeEnv to get a ConfigWithoutManager, make the manager, then return a ConfigWithManager. Unfortunately the whole thing screeches to a halt with:

No instance for (Var ())

So that approach doesn't work. I can work around it by using Bool instead of (), but that's not great. It would be nice if Envy could provide a Var instance for (). Obviously unit doesn't convey any information, so it doesn't make a ton of sense to use it in an environment variable. But it can be handy in situations like this.

No `Var` instance for `Last`

There is an instance for Var instance for Maybe but not for the newtype Last. Both Last and First are types that show up in option records. If the following could be added:

deriving instance (Var a, Typeable a) => Var (Last a)
deriving instance (Var a, Typeable a) => Var (First a)

ToEnv purpose

instance ToEnv PGConfig where
  toEnv = makeEnv 
       [ "PG_HOST" .= ("localhost" :: String)
       , "PG_PORT" .= (5432        :: Word16)
       , "PG_USER" .= ("user"      :: String)
       , "PG_PASS" .= ("pass"      :: String)
       , "PG_DB"   .= ("db"        :: String)
       ]

Why wouldn't you want toEnv to use data from the specific instance (:: a -> EnvList a), so that I could e.g. make PGConfig "https://myhost" 5432 "itsme" "secretpass" "dbname" and then output those values rather than hardcoded values for a type at large?

Race conditions in testing environmental variables

We found a race condition error while trying to write environmental unit/property tests. Does this come up with Envy's Quickcheck tests? This is likely more of a problem underlying System.Environment, but I'm wondering if there's a way to deal with it within Envy. Here's an example definition:

module Types where

import BasicPrelude
import System.Envy

data Conf = Conf
  { _cConfFile      :: Maybe String   
  , _cPort          :: Maybe Word32   
  , _cTimeout       :: Maybe Word32
  } deriving ( Eq, Show )

instance FromEnv Conf where
  fromEnv =
    Conf                  <$>
      envMaybe "CONFFILE" <*>
      envMaybe "PORT"     <*>
      envMaybe "TIMEOUT" 

instance ToEnv Conf where
  toEnv Conf{..} =
    makeEnv [ "CONFFILE" .= _cConfFile
            , "PORT"     .= _cPort
            , "TIMEOUT"  .= _cTimeout
            ]

and an example test...

module Test
  ( tests
  ) where

import BasicPrelude
import Data.Text
import System.Environment
import System.Envy
import Test.Tasty
import Test.Tasty.HUnit

testEnv :: TestTree
testEnv =
  testGroup "Environmental configuration unit test"
    [ testCase "Empty configuration" $ do
        unsetEnv "SKYLARK_CONFFILE"
        unsetEnv "SKYLARK_PORT"
        unsetEnv "SKYLARK_TIMEOUT"
        c <- decodeEnv :: IO (Either String Conf)
        c @?= Right Conf { _cConfFile = Nothing
                         , _cPort = Nothing
                         , _cTimeout = Nothing
                         }
    , testCase "Port and Timeout" $ do
        unsetEnv "SKYLARK_CONFFILE"
        setEnv "SKYLARK_PORT" "1"
        setEnv "SKYLARK_TIMEOUT" "1"
        c <- decodeEnv :: IO (Either String Conf)
        c @?= Right Conf { _cConfFile = Nothing
                         , _cPort = Just 1
                         , _cTimeout = Just 1
                         }
    ]

This test can sometimes pass, or it fail, with the decoded environment in one test case being not the one set in that specific test case. For example, the first case unsetting the environmental variables can instead read the values set in the second test case. This also appears with a Quickcheck not too different from the one committed with Envy (https://gist.github.com/mookerji/d6c9fe48bc35e16bd5690).

write against MonadIO

Wouldn't it make sense to use a MonadIO m instead of IO for the output.
Also, for the retrieval, one might want to separate the "capacity" to read/write named variable from its use. one capacity whose implementation could be provided by ... a MonadIO constrained monad :)

instances for tuples

It could be nice to provide FromEnv/ToEnv instances for tuples, including the empty tuple. This would allow users the ability to assemble their environment out of discrete parts.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.