Merge pull request #245 from mgold/dev

Convert Color, Dict, and Set docs.
This commit is contained in:
Evan Czaplicki 2013-09-09 22:47:44 -07:00
commit 66add54195
3 changed files with 137 additions and 69 deletions

View file

@ -1,31 +1,52 @@
module Color where
{-| Library for working with colors. Includes
[RGB](https://en.wikipedia.org/wiki/RGB_color_model) and
[HSV](http://en.wikipedia.org/wiki/HSL_and_HSV) creation, gradients, and
built-in names.
# Creation
@docs rgb, rgba, hsv, hsva, grayscale, greyscale
# From Other Colors
@docs complementary
# Gradients
@docs linear radial
# Built-in Colors
These come from the [Tango
palette](http://tango.freedesktop.org/Tango_Icon_Theme_Guidelines).
@docs red, orange, yellow, green, blue, purple, brown, black, white, grey, gray, charcoal, lightRed, lightOrange, lightYellow, lightGreen, lightBlue, lightPurple, lightBrown, lightGrey, lightGray, lightCharcoal, darkRed, darkOrange, darkYellow, darkGreen, darkBlue, darkPurple, darkBrown, darkGrey, darkGray, darkCharcoal
-}
import Native.Color
import Basics ((-))
data Color = Color Int Int Int Float
-- Create RGB colors with an alpha component for transparency.
-- The alpha component is specified with numbers between 0 and 1.
{-| Create RGB colors with an alpha component for transparency.
The alpha component is specified with numbers between 0 and 1. -}
rgba : Int -> Int -> Int -> Float -> Color
rgba = Color
-- Create RGB colors from numbers between 0 and 255 inclusive.
{-| Create RGB colors from numbers between 0 and 255 inclusive. -}
rgb : Int -> Int -> Int -> Color
rgb r g b = Color r g b 1
lightYellow = Color 255 233 79 1
yellow = Color 237 212 0 1
darkYellow = Color 196 160 0 1
lightRed = Color 239 41 41 1
red = Color 204 0 0 1
darkRed = Color 164 0 0 1
lightOrange = Color 252 175 62 1
orange = Color 245 121 0 1
darkOrange = Color 206 92 0 1
lightBrown = Color 233 185 110 1
brown = Color 193 125 17 1
darkBrown = Color 143 89 2 1
lightYellow = Color 255 233 79 1
yellow = Color 237 212 0 1
darkYellow = Color 196 160 0 1
lightGreen = Color 138 226 52 1
green = Color 115 210 22 1
@ -39,9 +60,9 @@ lightPurple = Color 173 127 168 1
purple = Color 117 80 123 1
darkPurple = Color 92 53 102 1
lightRed = Color 239 41 41 1
red = Color 204 0 0 1
darkRed = Color 164 0 0 1
lightBrown = Color 233 185 110 1
brown = Color 193 125 17 1
darkBrown = Color 143 89 2 1
black = Color 0 0 0 1
white = Color 255 255 255 1
@ -58,25 +79,24 @@ lightCharcoal = Color 136 138 133 1
charcoal = Color 85 87 83 1
darkCharcoal = Color 46 52 54 1
{-| Produce a gray based on the input. 0 is white, 1 is black. -}
grayscale : Float -> Color
grayscale p = hsv 0 0 (1-p)
greyscale p = hsv 0 0 (1-p)
-- Produce a “complementary color”.
-- The two colors will accent each other.
{-| Produce a “complementary color”.
The two colors will accent each other. -}
complement : Color -> Color
complement = Native.Color.complement
-- Create [HSV colors](http://en.wikipedia.org/wiki/HSL_and_HSV)
-- with an alpha component for transparency.
{-| Create [HSV colors](http://en.wikipedia.org/wiki/HSL_and_HSV)
with an alpha component for transparency. -}
hsva : Float -> Float -> Float -> Float -> Color
hsva = Native.Color.hsva
-- Create [HSV colors](http://en.wikipedia.org/wiki/HSL_and_HSV).
-- This is very convenient for creating colors that cycle and shift.
-- Hue is an angle and should be given in standard Elm angles (radians).
--
-- hsv (degrees 240) 1 1 == blue
{-| Create [HSV colors](http://en.wikipedia.org/wiki/HSL_and_HSV). This is very
convenient for creating colors that cycle and shift. Hue is an angle and should
be given in standard Elm angles (radians). -}
hsv : Float -> Float -> Float -> Color
hsv = Native.Color.hsv
@ -84,17 +104,17 @@ data Gradient
= Linear (Float,Float) (Float,Float) [(Float,Color)]
| Radial (Float,Float) Float (Float,Float) Float [(Float,Color)]
-- Create a linear gradient. Takes a start and end point and then a series
-- of “color stops” that indicate how to interpolate between
-- the start and end points. See [this example](/edit/examples/Elements/LinearGradient.elm) for
-- a more visual explanation.
{-| Create a linear gradient. Takes a start and end point and then a series of
“color stops” that indicate how to interpolate between the start and
end points. See [this example](/edit/examples/Elements/LinearGradient.elm) for a
more visual explanation. -}
linear : (number, number) -> (number, number) -> [(Float,Color)] -> Gradient
linear = Linear
-- Create a radial gradient. First takes a start point and inner radius.
-- Then takes an end point and outer radius. It then takes a series
-- of “color stops” that indicate how to interpolate between
-- the inner and outer circles. See [this example](/edit/examples/Elements/RadialGradient.elm) for
-- a more visual explanation.
{-| Create a radial gradient. First takes a start point and inner radius. Then
takes an end point and outer radius. It then takes a series of “color
stops” that indicate how to interpolate between the inner and outer
circles. See [this example](/edit/examples/Elements/RadialGradient.elm) for a
more visual explanation. -}
radial : (number,number) -> number -> (number,number) -> number -> [(Float,Color)] -> Gradient
radial = Radial

View file

@ -8,6 +8,30 @@ module Dict (empty,singleton,insert
,toList,fromList
) where
{-|A dictionary mapping unique keys to values. The keys can be any comparable
type. This includes `Int`, `Float`, `Time`, `Char`, `String`, and tuples or
lists of comparable types.
Insert, remove, and query operations all take *O(log n)* time.
# Build
@docs empty, singleton, insert, remove
# Query
@docs member, lookup, findWithDefault
# Combine
@docs union, intersect, diff
# Lists
@docs keys, values, toList, fromList
# Transform
@docs map, foldl, foldr
-}
import open Basics
import open Maybe
import Native.Error
@ -18,7 +42,7 @@ data NColor = Red | Black
data Dict k v = RBNode NColor k v (Dict k v) (Dict k v) | RBEmpty
-- Create an empty dictionary.
{-| Create an empty dictionary. -}
empty : Dict comparable v
empty = RBEmpty
@ -116,7 +140,7 @@ max t =
}
--}
-- Lookup the value associated with a key.
{-| Lookup the value associated with a key. -}
lookup : comparable -> Dict comparable v -> Maybe v
lookup k t =
case t of
@ -127,8 +151,8 @@ lookup k t =
EQ -> Just v
GT -> lookup k r
-- Find the value associated with a key. If the key is not found,
-- return the default value.
{-| Find the value associated with a key. If the key is not found,
return the default value. -}
findWithDefault : v -> comparable -> Dict comparable v -> v
findWithDefault base k t =
case t of
@ -152,7 +176,7 @@ find k t =
}
--}
-- Determine if a key is in a dictionary.
{-| Determine if a key is in a dictionary. -}
member : comparable -> Dict comparable v -> Bool
-- Does t contain k?
member k t = isJust <| lookup k t
@ -208,8 +232,8 @@ ensureBlackRoot t =
RBNode Red k v l r -> RBNode Black k v l r
_ -> t
-- Insert a key-value pair into a dictionary. Replaces value when there is
-- a collision.
{-| Insert a key-value pair into a dictionary. Replaces value when there is
a collision. -}
insert : comparable -> v -> Dict comparable v -> Dict comparable v
insert k v t = -- Invariant: t is a valid left-leaning rb tree
let ins t =
@ -231,7 +255,7 @@ insert k v t = -- Invariant: t is a valid left-leaning rb tree
else new_t)
--}
-- Create a dictionary with one key-value pair.
{-| Create a dictionary with one key-value pair. -}
singleton : comparable -> v -> Dict comparable v
singleton k v = insert k v RBEmpty
@ -312,8 +336,8 @@ deleteMax t =
in ensureBlackRoot (del t)
--}
-- Remove a key-value pair from a dictionary. If the key is not found,
-- no changes are made.
{-| Remove a key-value pair from a dictionary. If the key is not found,
no changes are made. -}
remove : comparable -> Dict comparable v -> Dict comparable v
remove k t =
let eq_and_noRightNode t =
@ -346,58 +370,58 @@ remove k t =
Native.Error.raise "invariants broken after remove")
--}
-- Apply a function to all values in a dictionary.
{-| Apply a function to all values in a dictionary. -}
map : (a -> b) -> Dict comparable a -> Dict comparable b
map f t =
case t of
RBEmpty -> RBEmpty
RBNode c k v l r -> RBNode c k (f v) (map f l) (map f r)
-- Fold over the key-value pairs in a dictionary, in order from lowest
-- key to highest key.
{-| Fold over the key-value pairs in a dictionary, in order from lowest
key to highest key. -}
foldl : (comparable -> v -> b -> b) -> b -> Dict comparable v -> b
foldl f acc t =
case t of
RBEmpty -> acc
RBNode _ k v l r -> foldl f (f k v (foldl f acc l)) r
-- Fold over the key-value pairs in a dictionary, in order from highest
-- key to lowest key.
{-| Fold over the key-value pairs in a dictionary, in order from highest
key to lowest key. -}
foldr : (comparable -> v -> b -> b) -> b -> Dict comparable v -> b
foldr f acc t =
case t of
RBEmpty -> acc
RBNode _ k v l r -> foldr f (f k v (foldr f acc r)) l
-- Combine two dictionaries. If there is a collision, preference is given
-- to the first dictionary.
{-| Combine two dictionaries. If there is a collision, preference is given
to the first dictionary. -}
union : Dict comparable v -> Dict comparable v -> Dict comparable v
union t1 t2 = foldl insert t2 t1
-- Keep a key-value pair when its key appears in the second dictionary.
-- Preference is given to values in the first dictionary.
{-| Keep a key-value pair when its key appears in the second dictionary.
Preference is given to values in the first dictionary. -}
intersect : Dict comparable v -> Dict comparable v -> Dict comparable v
intersect t1 t2 =
let combine k v t = if k `member` t2 then insert k v t else t
in foldl combine empty t1
-- Keep a key-value pair when its key does not appear in the second dictionary.
-- Preference is given to the first dictionary.
{-| Keep a key-value pair when its key does not appear in the second dictionary.
Preference is given to the first dictionary. -}
diff : Dict comparable v -> Dict comparable v -> Dict comparable v
diff t1 t2 = foldl (\k v t -> remove k t) t1 t2
-- Get all of the keys in a dictionary.
{-| Get all of the keys in a dictionary. -}
keys : Dict comparable v -> [comparable]
keys t = foldr (\k v acc -> k :: acc) [] t
-- Get all of the values in a dictionary.
{-| Get all of the values in a dictionary. -}
values : Dict comparable v -> [v]
values t = foldr (\k v acc -> v :: acc) [] t
-- Convert a dictionary into an association list of key-value pairs.
{-| Convert a dictionary into an association list of key-value pairs. -}
toList : Dict comparable v -> [(comparable,v)]
toList t = foldr (\k v acc -> (k,v) :: acc) [] t
-- Convert an association list into a dictionary.
{-| Convert an association list into a dictionary. -}
fromList : [(comparable,v)] -> Dict comparable v
fromList assocs = List.foldl (\(k,v) d -> insert k v d) empty assocs

View file

@ -6,61 +6,85 @@ module Set (empty,singleton,insert,remove
,toList,fromList
) where
{-|A set of unique values. The values can be any comparable type. This includes
`Int`, `Float`, `Time`, `Char`, `String`, and tuples or lists of comparable
types.
Insert, remove, and query operations all take *O(log n)* time.
# Build
@docs empty, singleton, insert, remove
# Query
@docs member
# Combine
@docs union, intersect, diff
# Lists
@docs toList, fromList
# Transform
@docs map, foldl, foldr
-}
import Maybe (Maybe)
import Dict as Dict
import List as List
type Set t = Dict.Dict t ()
-- Create an empty set.
{-| Create an empty set. -}
empty : Set comparable
empty = Dict.empty
-- Create a set with one value.
{-| Create a set with one value. -}
singleton : comparable -> Set comparable
singleton k = Dict.singleton k ()
-- Insert a value into a set.
{-| Insert a value into a set. -}
insert : comparable -> Set comparable -> Set comparable
insert k = Dict.insert k ()
-- Remove a value from a set. If the value is not found, no changes are made.
{-| Remove a value from a set. If the value is not found, no changes are made.
-}
remove : comparable -> Set comparable -> Set comparable
remove = Dict.remove
-- Determine if a value is in a set.
{-| Determine if a value is in a set. -}
member : comparable -> Set comparable -> Bool
member = Dict.member
-- Get the union of two sets. Keep all values.
{-| Get the union of two sets. Keep all values. -}
union : Set comparable -> Set comparable -> Set comparable
union = Dict.union
-- Get the intersection of two sets. Keeps values that appear in both sets.
{-| Get the intersection of two sets. Keeps values that appear in both sets. -}
intersect : Set comparable -> Set comparable -> Set comparable
intersect = Dict.intersect
-- Get the difference between the first set and the second. Keeps values
-- that do not appear in the second set.
{-| Get the difference between the first set and the second. Keeps values
that do not appear in the second set. -}
diff : Set comparable -> Set comparable -> Set comparable
diff = Dict.diff
-- Convert a set into a list.
{-| Convert a set into a list. -}
toList : Set comparable -> [comparable]
toList = Dict.keys
-- Convert a list into a set, removing any duplicates.
{-| Convert a list into a set, removing any duplicates. -}
fromList : [comparable] -> Set comparable
fromList xs = List.foldl insert empty xs
-- Fold over the values in a set, in order from lowest to highest.
{-| Fold over the values in a set, in order from lowest to highest. -}
foldl : (comparable -> b -> b) -> b -> Set comparable -> b
foldl f b s = Dict.foldl (\k _ b -> f k b) b s
-- Fold over the values in a set, in order from highest to lowest.
{-| Fold over the values in a set, in order from highest to lowest. -}
foldr : (comparable -> b -> b) -> b -> Set comparable -> b
foldr f b s = Dict.foldr (\k _ b -> f k b) b s
-- Map a function onto a set, creating a new set with no duplicates.
{-| Map a function onto a set, creating a new set with no duplicates. -}
map : (comparable -> comparable') -> Set comparable -> Set comparable'
map f s = fromList (List.map f (toList s))