module Web.Lightning.Utilities
(
omitNulls
, createPayLoad
, createDataPayLoad
, addSessionId
, getLinks
, getNodes
, getPoints
, getPoints3
, validateBin
, validateColor
, validateColorMap
, validateSize
, validateAlpha
, validateThickness
, validateIndex
, validateCoordinates
, validateCoordinates3
, validateRegion
, validateConn
, defaultBaseURL
)
where
import Data.Aeson
import qualified Data.Text as T
import Web.Lightning.Types.Error
omitNulls :: [(T.Text, Value)]
-> Value
omitNulls = object . filter notNull where
notNull (_, Null) = False
notNull _ = True
createPayLoad :: T.Text
-> Value
-> Value
createPayLoad t p = object [("type", toJSON t), ("data", p)]
createDataPayLoad :: Value
-> Value
createDataPayLoad p = object [("data", p)]
addSessionId :: T.Text
-> T.Text
-> T.Text
addSessionId url sId = url `T.append` "/sessions/" `T.append` sId
getLinks :: [[Double]]
-> [[Double]]
getLinks conn
| length conn == length (head conn) = s1 (zipWithIndex conn)
| otherwise = s4 conn
where s1 = concatMap (\(row, i) -> s3 i (s2 (zipWithIndex row)))
s2 = filter (\(x, _) -> x /= 0)
s3 i = map (\(x, j) -> [i, j, x] :: [Double])
s4 xs = case length xs of
2 -> xs
3 -> map (\l -> [head l, l !! 1, 1.0]) xs
_ -> [[]]
zipWithIndex :: (Enum b, Num b) => [a] -> [(a, b)]
zipWithIndex [] = []
zipWithIndex xs = zipWith (\i el -> (i, el)) xs [0..]
getNodes :: [[Double]]
-> [Int]
getNodes conn
| length conn == length (head conn) = [0..length conn 1]
| otherwise = [0..n 1]
where n = floor $ maximum $ map maximum conn
getPoints :: [Double]
-> [Double]
-> [[Double]]
getPoints xs ys = map (\(x, y) -> [x, y]) $ zip xs ys
getPoints3 :: [Double]
-> [Double]
-> [Double]
-> [[Double]]
getPoints3 xs ys zs = map (\(x, y, z) -> [x, y, z]) $ zip3 xs ys zs
validateBin :: Maybe [Double]
-> Either LightningError (Maybe [Double])
validateBin = return
validateColor :: Maybe [Int]
-> Either LightningError (Maybe [Int])
validateColor (Just colors)
| length colors == 3 = Right (Just colors)
| otherwise = Left $ ValidationError "Color must have three values."
validateColor Nothing = Right Nothing
validateColorMap :: Maybe T.Text
-> Either LightningError (Maybe T.Text)
validateColorMap cm@(Just cmv) =
if cmv `elem` colorMaps
then Right cm
else Left $ ValidationError "Invalid color map specified."
where colorMaps = ["BrBG", "PiYG", "PRGn", "PuOr", "RdBu", "RdGy", "RdYlBu",
"RdYlGn", "Spectral", "Blues", "BuGn", "BuPu", "GnBu",
"Greens", "Greys", "Oranges", "OrRd", "PuBu", "PuBuGn",
"PuRd", "Purples", "RdPu", "Reds", "YlGn", "YlGnBu",
"YlOrBr", "YlOrRd", "Accent", "Dark2", "Paired", "Pastel1",
"Pastel2", "Set1", "Set2", "Set3", "Lightning"]
validateColorMap Nothing = Right Nothing
validateSize :: Maybe [Int]
-> Either LightningError (Maybe [Int])
validateSize size = validateGreaterThan0 size msg
where msg = "Sizes cannot be 0 or negative."
validateAlpha :: Maybe [Double]
-> Either LightningError (Maybe [Double])
validateAlpha alpha = validateGreaterThan0 alpha msg
where msg = "Alpha cannot be 0 or negative."
validateThickness :: Maybe [Int]
-> Either LightningError (Maybe [Int])
validateThickness thickness = validateGreaterThan0 thickness msg
where msg = "Thickness cannot be 0 or negative."
validateIndex :: Maybe [Int]
-> Either LightningError (Maybe [Int])
validateIndex index@(Just idx)
| not (null idx) = Right index
| otherwise = Left $ ValidationError "Index must be non-singleton."
validateIndex Nothing = Right Nothing
validateCoordinates :: [Double]
-> [Double]
-> Either LightningError ([Double], [Double])
validateCoordinates xs ys =
if length xs == length ys
then Right (xs, ys)
else Left $ ValidationError "x and y vectors must be the same length."
validateCoordinates3 :: [Double]
-> [Double]
-> [Double]
-> Either LightningError ([Double],[Double],[Double])
validateCoordinates3 xs ys zs =
if (length xs == length ys) && (length ys == length zs)
then Right (xs, ys, zs)
else Left $ ValidationError "x, y, and z vectors must be the same length."
validateRegion :: [T.Text]
-> Either LightningError [T.Text]
validateRegion regions =
if checkTwo || checkThree
then Right regions
else Left $ ValidationError msg
where
msg = "All region names must be all 2 letters or all 3 letters."
checkTwo = all (\x -> T.length x == 2) regions
checkThree = all (\x -> T.length x == 3) regions
validateConn :: [[Double]]
-> Either LightningError [[Double]]
validateConn conn
| length conn == length (head conn) = Right conn
| length (head conn) == 2 = Right conn
| length (head conn) == 3 = Right conn
| otherwise = Left $ ValidationError msg
where
msg = "Too many entries per link, must be 2 or 3."
validateGreaterThan0 :: (Ord a, Num a) => Maybe [a]
-> T.Text
-> Either LightningError (Maybe [a])
validateGreaterThan0 vals@(Just vs) msg =
if any (<= 0) vs
then Left $ ValidationError msg
else Right vals
validateGreaterThan0 Nothing _ = Right Nothing
defaultBaseURL :: T.Text
defaultBaseURL = "http://localhost:3000"