dynamic-0.1.0: A dynamic type for Haskell

Safe HaskellNone
LanguageHaskell2010

Dynamic

Contents

Description

Support dynamic typing.

Synopsis

Documentation

data Dynamic Source #

The dynamic type.

Instances
Enum Dynamic Source #

Treats the dynamic as a double.

Instance details

Defined in Dynamic

Eq Dynamic Source # 
Instance details

Defined in Dynamic

Methods

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

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

Fractional Dynamic Source # 
Instance details

Defined in Dynamic

Integral Dynamic Source #

Implemented via Dynamic.

Instance details

Defined in Dynamic

Data Dynamic Source # 
Instance details

Defined in Dynamic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dynamic -> c Dynamic #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dynamic #

toConstr :: Dynamic -> Constr #

dataTypeOf :: Dynamic -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dynamic) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dynamic) #

gmapT :: (forall b. Data b => b -> b) -> Dynamic -> Dynamic #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dynamic -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dynamic -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dynamic -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dynamic -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dynamic -> m Dynamic #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dynamic -> m Dynamic #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dynamic -> m Dynamic #

Num Dynamic Source #

Converts everything to a double.

Instance details

Defined in Dynamic

Ord Dynamic Source # 
Instance details

Defined in Dynamic

Real Dynamic Source #

Implemented via toDouble.

Instance details

Defined in Dynamic

Show Dynamic Source #

Dumps it to JSON.

Instance details

Defined in Dynamic

IsString Dynamic Source #

Makes a Dynamic.

Instance details

Defined in Dynamic

Methods

fromString :: String -> Dynamic #

Generic Dynamic Source # 
Instance details

Defined in Dynamic

Associated Types

type Rep Dynamic :: Type -> Type #

Methods

from :: Dynamic -> Rep Dynamic x #

to :: Rep Dynamic x -> Dynamic #

Semigroup Dynamic Source #

Nulls are identity, arraysdicts join, string + doublebool append everything else is toText x <> toText y.

Instance details

Defined in Dynamic

ToJSON Dynamic Source #

Pretty much a 1:1 correspondance.

Instance details

Defined in Dynamic

FromJSON Dynamic Source #

Does what you'd expect.

Instance details

Defined in Dynamic

FromRecord Dynamic Source #

Produces an array representing a row of columns.

Instance details

Defined in Dynamic

ToRecord Dynamic Source #

Renders the elements of containers, or else a singleton.

Instance details

Defined in Dynamic

Methods

toRecord :: Dynamic -> Record #

FromNamedRecord Dynamic Source #

Produces a dictionary representing a row of columns.

Instance details

Defined in Dynamic

ToNamedRecord Dynamic Source #

Just works on dictionaries.

Instance details

Defined in Dynamic

FromField Dynamic Source #

Tries to figure out decimals, coerce true/false into Dynamic, and null into Null.

Instance details

Defined in Dynamic

ToField Dynamic Source #

Identity for strings, else JSON output.

Instance details

Defined in Dynamic

Methods

toField :: Dynamic -> Field #

type Rep Dynamic Source # 
Instance details

Defined in Dynamic

Accessors

(!) :: Dynamic -> Dynamic -> Dynamic infixl 9 Source #

object ! key to access the field at key.

set :: Dynamic -> Dynamic -> Dynamic -> Dynamic Source #

set key value object -- set the field's value.

modify :: Dynamic -> (Dynamic -> Dynamic) -> Dynamic -> Dynamic Source #

modify k f obj -- modify the value at key.

del :: Dynamic -> Dynamic -> Dynamic Source #

del k obj -- delete the key k in obj.

Input

fromJson :: Text -> Dynamic Source #

Read JSON into a Dynamic.

fromCsv :: Text -> [[Dynamic]] Source #

Read CSV into a list of rows with columns (don't use column names).

fromCsvNamed :: Text -> [Dynamic] Source #

Read CSV into a list of rows (use column names).

fromJsonFile :: FilePath -> IO Dynamic Source #

Same as fromJson but from a file.

fromCsvFile :: FilePath -> IO [[Dynamic]] Source #

Same as fromCsv but from a file.

fromCsvFileNamed :: FilePath -> IO [Dynamic] Source #

Same as fromCsvFileNamed but from a file.

fromList :: [Dynamic] -> Dynamic Source #

Convert a list of dynamics to a dynamic list.

fromDict :: [(Dynamic, Dynamic)] -> Dynamic Source #

Convert a list of key/pairs to a dynamic dictionary.

Ouput

toJson :: Dynamic -> Text Source #

Produces a JSON representation of the string.

toCsv :: [Dynamic] -> Text Source #

Produces a JSON representation of the string.

toCsvNamed :: [Dynamic] -> Text Source #

Produces a JSON representation of the string.

toJsonFile :: FilePath -> Dynamic -> IO () Source #

Produces a JSON representation of the string.

toCsvFile :: FilePath -> [Dynamic] -> IO () Source #

Produces a JSON representation of the string.

toDouble :: Dynamic -> Double Source #

Convert a dynamic value to a Double.

toInt :: Dynamic -> Int Source #

Convert a dynamic value to an Int.

toBool :: Dynamic -> Bool Source #

Convert to a boolean.

toList :: Dynamic -> [Dynamic] Source #

Convert to a list.

toKeys :: Dynamic -> [Dynamic] Source #

Get all the keys.

toElems :: Dynamic -> [Dynamic] Source #

Get all the elems.

Web requests

get Source #

Arguments

:: Dynamic 
-> [(Dynamic, Dynamic)]

Headers.

-> IO Text 

HTTP GET request for text content.

post Source #

Arguments

:: Dynamic

URL.

-> [(Dynamic, Dynamic)]

Headers.

-> Dynamic

Body.

-> IO Text 

HTTP POST request for text content.

getJson Source #

Arguments

:: Dynamic 
-> [(Dynamic, Dynamic)]

Headers.

-> IO Dynamic 

HTTP GET request for text content.

postJson Source #

Arguments

:: Dynamic

URL.

-> [(Dynamic, Dynamic)]

Headers.

-> Dynamic

Body.

-> IO Dynamic 

HTTP POST request for JSON content.