*.#*
html/
/GUI/
-*.png
\ No newline at end of file
+/img/Shapes.hs
\ No newline at end of file
module RMCA.GUI.Board where
-import Data.Array
-import Game.Board.BasicTurnGame
-import Graphics.UI.Gtk
-import RMCA.Semantics hiding (Action)
+import Control.Monad
+import Data.Array
+import qualified Data.Bifunctor as BF
+import Data.Maybe
+import Data.Ratio
+import Game.Board.BasicTurnGame
+import Graphics.UI.Gtk hiding (Action)
+import Graphics.UI.Gtk.Board.BoardLink
+import RMCA.Semantics
-newtype GUIBoard = GUIBoard (GameState Int Cell () Action)
+newtype GUIBoard = GUIBoard (GameState Int Tile Player Action)
-boardToList :: Board -> [(Int,Int,Cell)]
-boardToList = map (\((x,y),z) -> (x,y,z)) . assocs
+data Tile = Tile
+data Player = Player
+
+tileW :: Int
+tileW = 35
+
+tileH :: Int
+tileH = round (sqrt 3 * fromIntegral tileW / 3)
+
+hexW :: Int
+hexW = round (4 * fromIntegral tileW / 3)
+
+boardToTile :: [(Int,Int,Tile)]
+boardToTile = [(x,y,Tile) | (x,y) <- range ( (xMin-1,yMin)
+ , (xMax+1,yMax+1))]
+ where (xMax,yMax) = BF.second (*2) $ neighbor N nec
+ (xMin,yMin) = BF.second (*2) swc
+
+boardToPiece :: Board -> [(Int,Int,Player,Action)]
+boardToPiece = map placePiece . filter (onBoard . fst) . assocs
+ where placePiece :: (Pos,Cell) -> (Int,Int,Player,Action)
+ placePiece ((x,y),(a,_)) = let y' = 2*(-y) + x `mod` 2 in
+ (x,y',Player,a)
+
+
+na = NoteAttr {
+ naArt = Accent13,
+ naDur = 1 % 1,
+ naOrn = Ornaments Nothing [] NoSlide
+ }
initGUIBoard :: GUIBoard
initGUIBoard = GUIBoard $ GameState
- { curPlayer' = ()
- , boardPos = boardToList $ makeBoard []
- , boardPieces' = []
+ { curPlayer' = Player
+ , boardPos = boardToTile
+ , boardPieces' = boardToPiece $ makeBoard [((0,5), mkCell (ChDir True na NE))]
}
-
+{-
instance Show GUIBoard where
show _ = "lol"
-
-instance PlayableGame GUIBoard Int Cell () Action where
- curPlayer _ = ()
+-}
+instance PlayableGame GUIBoard Int Tile Player Action where
+ curPlayer _ = Player
allPos (GUIBoard game) = boardPos game
allPieces (GUIBoard game) = boardPieces' game
moveEnabled _ = True
- canMove _ _ _ = True
- canMoveTo _ _ _ _ = True
-
-pixbufFrom :: (Int, Int) -> Cell -> IO Pixbuf
-pixbufFrom (hexW,hexH) (a,_) = do
- let pixbufScaleSimple' p = pixbufScaleSimple p hexW hexH InterpBilinear
- actionToFile = case a of
- Inert -> "img/hexOff.png"
- Absorb -> "img/stop.svg"
- Stop _ -> "img/stop.svg"
- ChDir True _ _ -> "img/start.svg"
- ChDir False _ _ -> "img/ric.svg"
- Split _ -> "img/split.svg"
- pixbufComposeAct p pa =
- pixbufComposite p pa 0 0 hexW hexH 0 0 1 1 InterpBilinear 255
- pixbufOn <- pixbufScaleSimple' =<< pixbufNewFromFile "img/hexOff.png"
- pixbufAct <- pixbufScaleSimple' =<< pixbufNewFromFile actionToFile
- pixbufComposeAct pixbufOn pixbufAct
- return pixbufAct
+ canMove (GUIBoard game) _ (x,y)
+ | Just (_,p) <- getPieceAt game (x,y)
+ , Inert <- p = False
+ | otherwise = True{-
+ canMoveTo _ _ _ (x,y)
+ | (x `mod` 2 == 0 && y `mod` 2 == 0) || (x `mod` 2 /= 0 && y `mod` 2 /= 0)
+ = True
+ | otherwise = False-}
+ canMoveTo _ _ _ _ = True
+
+
+ move (GUIBoard game) _ iPos@(_,yi) fPos@(xf,yf) = [MovePiece iPos fPos']
+ where fPos'
+ | (xf `mod` 2 == 0 && yf `mod` 2 == 0)
+ || (xf `mod` 2 /= 0 && yf `mod` 2 /= 0) = (xf,yf)
+ | otherwise = (xf,yf+signum' (yf-yi))
+ signum' x
+ | x == 0 = 1
+ | otherwise = signum x
+
+
+
+ applyChange (GUIBoard game) (AddPiece pos@(x,y) _ piece) =
+ GUIBoard $ game { boardPieces' = bp' }
+ where bp' = (x,y,Player,piece):(
+ filter (\(x',y',_,_) -> (x',y') /= pos) $ boardPieces' game)
+
+ applyChange (GUIBoard game) (RemovePiece pos) =
+ (\g -> applyChange g (AddPiece pos Player Inert)) $
+ GUIBoard $ game { boardPieces' = bp' }
+ where bp' = filter (\(x',y',_,_) -> pos /= (x',y')) $ boardPieces' game
+
+ applyChange guiBoard@(GUIBoard game) (MovePiece iPos fPos)
+ | Just (_,p) <- getPieceAt game iPos
+ = applyChanges guiBoard [ RemovePiece iPos
+ , RemovePiece fPos
+ , AddPiece fPos Player p]
+ | otherwise = guiBoard
+
+initGame :: IO (Game GUIBoard Int Tile Player Action)
+initGame = do
+ pixbufs <- fileToPixbuf
+ tilePixbuf <- pixbufNew ColorspaceRgb False 8 tileW tileH
+ pixbufFill tilePixbuf 50 50 50 0
+ let pixPiece :: (Player,Action) -> Pixbuf
+ pixPiece (_,a) = fromJust $ lookup (actionToFile a) pixbufs
+ pixTile :: Tile -> Pixbuf
+ pixTile _ = tilePixbuf
+ visual = VisualGameAspects { tileF = pixTile
+ , pieceF = pixPiece
+ , bgColor = (1000,1000,1000)
+ , bg = Nothing
+ }
+
+ return $ Game visual initGUIBoard
+
+fileToPixbuf :: IO [(FilePath,Pixbuf)]
+fileToPixbuf = sequence $
+ map (\f -> uncurry (liftM2 (,))
+ ( return f
+ , pixbufNewFromFile f >>=
+ \p -> pixbufScaleSimple p hexW hexW InterpBilinear )) $
+ map ("img/" ++) $ ["hexOn.png","stop.svg","split.svg"] ++
+ concat [["start" ++ show d ++ ".svg","ric" ++ show d ++ ".svg"]
+ | d <- [N .. NW]]
+
+actionToFile :: Action -> FilePath
+actionToFile a = case a of
+ Inert -> "img/hexOn.png"
+ Absorb -> "img/stop.svg"
+ Stop _ -> "img/stop.svg"
+ ChDir True _ d -> "img/start" ++ show d ++ ".svg"
+ ChDir False _ d -> "img/ric" ++ show d ++ ".svg"
+ Split _ -> "img/split.svg"
-> Render ()
hexagon (backR, backG, backB) (frameR, frameG, frameB) (x,y) w = do
setSourceRGB frameR frameG frameB
- setLineWidth (0.05 * w)
+ setLineWidth (0.01 * w)
let a = 0.5*w
b = 0.87*w
import RMCA.Translator.Translator
import Graphics.UI.Gtk.Layout.BackgroundContainer
import RMCA.GUI.Board
+import Graphics.UI.Gtk.Board.BoardLink
import Control.Monad
import Data.Ratio
, containerChild := mainBox
, containerBorderWidth := 10
]
+ windowMaximize window
settingsBox <- vBoxNew False 0
boxPackEnd mainBox settingsBox PackNatural 0
boxPackStart buttonBox buttonRecord PackRepel 0
-- Board
- boardCont <- backgroundContainerNewWithPicture "ussr.png"
- containerAdd mainBox boardCont
+ boardCont <- backgroundContainerNew
+ game <- initGame
+ board <- attachGameRules game
+ --centerBoard <- alignmentNew 0.5 0.5 0 0
+ containerAdd boardCont board
+ --containerAdd boardCont centerBoard
+ boxPackStart mainBox boardCont PackNatural 0
--boxPackStart mainBox boardCont PackNatural 0
------------------------------------------------------------------------------
boardQueue <- newCBMVarRW []
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="ricE.svg"><metadata
+ id="metadata3428"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs3426" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="1366"
+ inkscape:window-height="716"
+ id="namedview3424"
+ showgrid="false"
+ inkscape:zoom="2.74"
+ inkscape:cx="38.50365"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="1"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="141.63348"
+ cy="-0.21214058"
+ r="100"
+ id="circle3419"
+ transform="matrix(0.70710678,0.70710678,-0.70710678,0.70710678,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="m 142.1,99.999985 -41.8,-54.2 20.4,10e-7 41.8,54.199999 -41.8,54.199995 -20.40001,1e-5 C 114.2,136.09998 128.2,118.09999 142.1,99.999985 Z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="99.999992"
+ cy="-100.3"
+ r="100"
+ id="circle3422"
+ transform="matrix(0,1,-1,0,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="utf-8"?>\r
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->\r
+<svg version="1.1" baseProfile="basic" id="Layer_1"\r
+ xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink" x="0px" y="0px" viewBox="0 0 200 200"\r
+ xml:space="preserve">\r
+<circle opacity="0.2" fill="#FFFFFF" cx="100.3" cy="100" r="100"/>\r
+<path id="svg_1" fill="#FFFFFF" d="M100.3,58.2L46.1,100V79.6l54.2-41.8l54.2,41.8V100C136.4,86.1,118.4,72.1,100.3,58.2z"/>\r
+<circle fill="none" stroke="#FFFFFF" stroke-width="5" stroke-miterlimit="10" cx="100.3" cy="100" r="100"/>\r
+</svg>\r
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="ricNE.svg"><metadata
+ id="metadata3428"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs3426" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="1366"
+ inkscape:window-height="716"
+ id="namedview3424"
+ showgrid="false"
+ inkscape:zoom="2.74"
+ inkscape:cx="38.50365"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="1"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="100.3"
+ cy="99.999992"
+ r="100"
+ id="circle3419"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="m 129.85706,70.442926 -67.882252,-8.768124 14.424979,-14.424978 67.882253,8.768124 8.76812,67.882242 -14.42498,14.425 c -2.96985,-22.62743 -5.79827,-45.254844 -8.76812,-67.882264 z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="141.63348"
+ cy="-0.21213959"
+ r="100"
+ id="circle3422"
+ transform="matrix(0.70710678,0.70710678,-0.70710678,0.70710678,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="ricNW.svg"><metadata
+ id="metadata3428"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs3426" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="1366"
+ inkscape:window-height="716"
+ id="namedview3424"
+ showgrid="false"
+ inkscape:zoom="2.74"
+ inkscape:cx="38.50365"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="1"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="-100"
+ cy="100.3"
+ r="100"
+ id="circle3419"
+ transform="matrix(0,-1,1,0,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="M 70.742937,70.442939 61.974813,138.32519 47.549835,123.90021 56.317959,56.01796 124.20021,47.249836 138.62519,61.674815 C 115.99777,64.644663 93.370354,67.47309 70.742937,70.442939 Z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="0.2121342"
+ cy="141.63348"
+ r="100"
+ id="circle3422"
+ transform="matrix(0.70710678,-0.70710678,0.70710678,0.70710678,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="ricS.svg"><metadata
+ id="metadata3428"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs3426" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="1366"
+ inkscape:window-height="716"
+ id="namedview3424"
+ showgrid="false"
+ inkscape:zoom="2.74"
+ inkscape:cx="38.50365"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="1"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="-0.21214058"
+ cy="-141.63348"
+ r="100"
+ id="circle3419"
+ transform="matrix(-0.70710678,0.70710678,-0.70710678,-0.70710678,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="m 100.30001,141.79999 54.2,-41.800005 0,20.400005 -54.2,41.8 -54.2,-41.8 -2e-6,-20.400006 c 18.100002,13.900006 36.1,27.900006 54.200002,41.800006 z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="-100.3"
+ cy="-99.999992"
+ r="100"
+ id="circle3422"
+ transform="scale(-1,-1)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="ricSE.svg"><metadata
+ id="metadata3428"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs3426" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="1366"
+ inkscape:window-height="716"
+ id="namedview3424"
+ showgrid="false"
+ inkscape:zoom="2.74"
+ inkscape:cx="38.50365"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="1"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="99.999992"
+ cy="-100.3"
+ r="100"
+ id="circle3419"
+ transform="matrix(0,1,-1,0,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="m 129.85707,129.55705 8.76812,-67.882255 14.42498,14.424982 -8.76812,67.882253 -67.882253,8.76812 -14.424984,-14.42498 c 22.627423,-2.96985 45.254837,-5.79827 67.882257,-8.76812 z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="-0.21213959"
+ cy="-141.63348"
+ r="100"
+ id="circle3422"
+ transform="matrix(-0.70710678,0.70710678,-0.70710678,-0.70710678,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="ricSW.svg"><metadata
+ id="metadata3428"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs3426" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="1366"
+ inkscape:window-height="716"
+ id="namedview3424"
+ showgrid="false"
+ inkscape:zoom="2.74"
+ inkscape:cx="38.50365"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="1"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="-100.3"
+ cy="-99.999992"
+ r="100"
+ id="circle3419"
+ transform="scale(-1,-1)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="m 70.742946,129.55706 67.882254,8.76812 -14.42498,14.42498 -67.882253,-8.76812 -8.768124,-67.882254 14.424981,-14.424983 c 2.969845,22.627423 5.798272,45.254837 8.768122,67.882257 z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="-141.63348"
+ cy="0.21213959"
+ r="100"
+ id="circle3422"
+ transform="matrix(-0.70710678,-0.70710678,0.70710678,-0.70710678,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="ricW.svg"><metadata
+ id="metadata3428"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs3426" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="1366"
+ inkscape:window-height="716"
+ id="namedview3424"
+ showgrid="false"
+ inkscape:zoom="2.74"
+ inkscape:cx="38.50365"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="1"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="-141.63348"
+ cy="0.212139"
+ r="100"
+ id="circle3419"
+ transform="matrix(-0.70710678,-0.70710678,0.70710678,-0.70710678,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="M 58.500005,99.999999 100.30001,154.2 l -20.400006,0 -41.799999,-54.200002 41.8,-54.2 20.400005,-1e-6 C 86.400004,63.899999 72.400005,81.899998 58.500005,99.999999 Z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="-99.999992"
+ cy="100.3"
+ r="100"
+ id="circle3422"
+ transform="matrix(0,-1,1,0,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="utf-8"?>\r
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->\r
+<svg version="1.1" baseProfile="basic" id="Layer_1"\r
+ xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink" x="0px" y="0px" viewBox="0 0 200 200"\r
+ xml:space="preserve">\r
+<circle opacity="0.2" fill="#FFFFFF" cx="100.3" cy="100" r="100"/>\r
+<circle fill="none" stroke="#FFFFFF" stroke-width="5" stroke-miterlimit="10" cx="100.3" cy="100" r="100"/>\r
+<circle fill="#FFFFFF" cx="100.2" cy="100.1" r="56.9"/>\r
+</svg>\r
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="startE.svg"><metadata
+ id="metadata14"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs12" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="720"
+ inkscape:window-height="480"
+ id="namedview10"
+ showgrid="false"
+ inkscape:zoom="1.18"
+ inkscape:cx="100"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="0"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="99.999992"
+ cy="-100.3"
+ r="100"
+ id="circle3"
+ transform="matrix(0,1,-1,0,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="m 142.1,99.999985 -41.8,-54.100001 20.4,10e-7 41.8,54.199995 -41.8,54.2 -20.40001,1e-5 C 114.2,136.19999 128.2,118.09999 142.1,99.999985 Z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="99.999992"
+ cy="-100.3"
+ r="100"
+ id="circle6"
+ transform="matrix(0,1,-1,0,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /><circle
+ cx="100.09998"
+ cy="-68.400009"
+ r="26.1"
+ id="circle8"
+ transform="matrix(0,1,-1,0,0,0)"
+ style="fill:#ffffff" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="utf-8"?>\r
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->\r
+<svg version="1.1" baseProfile="basic" id="Layer_1"\r
+ xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink" x="0px" y="0px" viewBox="0 0 200 200"\r
+ xml:space="preserve">\r
+<circle opacity="0.2" fill="#FFFFFF" cx="100.3" cy="100" r="100"/>\r
+<path id="svg_1" fill="#FFFFFF" d="M100.3,58.2L46.2,100V79.6l54.2-41.8l54.2,41.8V100C136.5,86.1,118.4,72.1,100.3,58.2z"/>\r
+<circle fill="none" stroke="#FFFFFF" stroke-width="5" stroke-miterlimit="10" cx="100.3" cy="100" r="100"/>\r
+<circle fill="#FFFFFF" cx="100.4" cy="131.9" r="26.1"/>\r
+</svg>\r
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="startNE.svg"><metadata
+ id="metadata14"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs12" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="720"
+ inkscape:window-height="480"
+ id="namedview10"
+ showgrid="false"
+ inkscape:zoom="1.18"
+ inkscape:cx="100"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="0"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="141.63348"
+ cy="-0.21213959"
+ r="100"
+ id="circle3"
+ transform="matrix(0.70710678,0.70710678,-0.70710678,0.70710678,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="m 129.85706,70.442926 -67.811542,-8.697414 14.424979,-14.424978 67.882243,8.768121 8.76813,67.882255 -14.42498,14.42499 c -2.96984,-22.62743 -5.86898,-45.325554 -8.83883,-67.952974 z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="141.63348"
+ cy="-0.21213959"
+ r="100"
+ id="circle6"
+ transform="matrix(0.70710678,0.70710678,-0.70710678,0.70710678,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /><circle
+ cx="141.73347"
+ cy="31.687855"
+ r="26.1"
+ id="circle8"
+ transform="matrix(0.70710678,0.70710678,-0.70710678,0.70710678,0,0)"
+ style="fill:#ffffff" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="startNW.svg"><metadata
+ id="metadata14"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs12" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="720"
+ inkscape:window-height="480"
+ id="namedview10"
+ showgrid="false"
+ inkscape:zoom="1.18"
+ inkscape:cx="100"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="0"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="0.2121342"
+ cy="141.63348"
+ r="100"
+ id="circle3"
+ transform="matrix(0.70710678,-0.70710678,0.70710678,0.70710678,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="M 70.742937,70.442939 62.045524,138.25448 47.620546,123.8295 56.38867,55.94725 124.27092,47.179126 138.6959,61.604104 c -22.62742,2.969848 -45.325546,5.868986 -67.952963,8.838835 z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="0.2121342"
+ cy="141.63348"
+ r="100"
+ id="circle6"
+ transform="matrix(0.70710678,-0.70710678,0.70710678,0.70710678,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /><circle
+ cx="0.31213266"
+ cy="173.53348"
+ r="26.1"
+ id="circle8"
+ transform="matrix(0.70710678,-0.70710678,0.70710678,0.70710678,0,0)"
+ style="fill:#ffffff" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="startS.svg"><metadata
+ id="metadata14"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs12" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="720"
+ inkscape:window-height="480"
+ id="namedview10"
+ showgrid="false"
+ inkscape:zoom="1.18"
+ inkscape:cx="100"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="0"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="-100.3"
+ cy="-99.999992"
+ r="100"
+ id="circle3"
+ transform="scale(-1,-1)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="m 100.30001,141.79999 54.1,-41.800005 0,20.400005 -54.2,41.8 -54.199999,-41.8 -2e-6,-20.400006 C 64.10001,113.89999 82.200008,127.89999 100.30001,141.79999 Z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="-100.3"
+ cy="-99.999992"
+ r="100"
+ id="circle6"
+ transform="scale(-1,-1)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /><circle
+ cx="-100.20001"
+ cy="-68.099998"
+ r="26.1"
+ id="circle8"
+ transform="scale(-1,-1)"
+ style="fill:#ffffff" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="startSE.svg"><metadata
+ id="metadata14"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs12" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="720"
+ inkscape:window-height="480"
+ id="namedview10"
+ showgrid="false"
+ inkscape:zoom="1.18"
+ inkscape:cx="100"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="0"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="-0.21213959"
+ cy="-141.63348"
+ r="100"
+ id="circle3"
+ transform="matrix(-0.70710678,0.70710678,-0.70710678,-0.70710678,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="m 129.85707,129.55705 8.69741,-67.811545 14.42498,14.424982 -8.76812,67.882253 -67.882253,8.76812 -14.424984,-14.42498 c 22.627422,-2.96984 45.325547,-5.86898 67.952967,-8.83883 z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="-0.21213959"
+ cy="-141.63348"
+ r="100"
+ id="circle6"
+ transform="matrix(-0.70710678,0.70710678,-0.70710678,-0.70710678,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /><circle
+ cx="-0.11214874"
+ cy="-109.73349"
+ r="26.1"
+ id="circle8"
+ transform="matrix(-0.70710678,0.70710678,-0.70710678,-0.70710678,0,0)"
+ style="fill:#ffffff" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="startSW.svg"><metadata
+ id="metadata14"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs12" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="720"
+ inkscape:window-height="480"
+ id="namedview10"
+ showgrid="false"
+ inkscape:zoom="1.18"
+ inkscape:cx="100"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="0"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="-141.63348"
+ cy="0.21213959"
+ r="100"
+ id="circle3"
+ transform="matrix(-0.70710678,-0.70710678,0.70710678,-0.70710678,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="m 70.742946,129.55706 67.811544,8.69741 -14.42498,14.42498 -67.882254,-8.76812 -8.768123,-67.882254 14.424981,-14.424983 c 2.969844,22.627423 5.868982,45.325547 8.838832,67.952967 z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="-141.63348"
+ cy="0.21213959"
+ r="100"
+ id="circle6"
+ transform="matrix(-0.70710678,-0.70710678,0.70710678,-0.70710678,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /><circle
+ cx="-141.53349"
+ cy="32.112133"
+ r="26.1"
+ id="circle8"
+ transform="matrix(-0.70710678,-0.70710678,0.70710678,-0.70710678,0,0)"
+ style="fill:#ffffff" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ version="1.1"
+ id="Layer_1"
+ x="0px"
+ y="0px"
+ viewBox="0 0 200 200"
+ xml:space="preserve"
+ inkscape:version="0.91 r13725"
+ sodipodi:docname="startW.svg"><metadata
+ id="metadata14"><rdf:RDF><cc:Work
+ rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" /><dc:title></dc:title></cc:Work></rdf:RDF></metadata><defs
+ id="defs12" /><sodipodi:namedview
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1"
+ objecttolerance="10"
+ gridtolerance="10"
+ guidetolerance="10"
+ inkscape:pageopacity="0"
+ inkscape:pageshadow="2"
+ inkscape:window-width="720"
+ inkscape:window-height="480"
+ id="namedview10"
+ showgrid="false"
+ inkscape:zoom="1.18"
+ inkscape:cx="100"
+ inkscape:cy="100"
+ inkscape:window-x="0"
+ inkscape:window-y="26"
+ inkscape:window-maximized="0"
+ inkscape:current-layer="Layer_1" /><circle
+ cx="-99.999992"
+ cy="100.3"
+ r="100"
+ id="circle3"
+ transform="matrix(0,-1,1,0,0,0)"
+ style="opacity:0.2;fill:#ffffff" /><path
+ id="svg_1"
+ d="M 58.500005,99.999999 100.30001,154.1 l -20.400005,0 -41.8,-54.200002 41.8,-54.199999 20.400005,-10e-7 c -13.900007,18.100001 -27.900005,36.2 -41.800005,54.300001 z"
+ inkscape:connector-curvature="0"
+ style="fill:#ffffff" /><circle
+ stroke-miterlimit="10"
+ cx="-99.999992"
+ cy="100.3"
+ r="100"
+ id="circle6"
+ transform="matrix(0,-1,1,0,0,0)"
+ style="fill:none;stroke:#ffffff;stroke-width:5;stroke-miterlimit:10" /><circle
+ cx="-99.899994"
+ cy="132.2"
+ r="26.1"
+ id="circle8"
+ transform="matrix(0,-1,1,0,0,0)"
+ style="fill:#ffffff" /></svg>
\ No newline at end of file
--- /dev/null
+<?xml version="1.0" encoding="utf-8"?>\r
+<!-- Generator: Adobe Illustrator 18.1.0, SVG Export Plug-In . SVG Version: 6.00 Build 0) -->\r
+<svg version="1.1" baseProfile="basic" id="Layer_1"\r
+ xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink" x="0px" y="0px" viewBox="0 0 200 200"\r
+ xml:space="preserve">\r
+<circle opacity="0.2" fill="#FFFFFF" cx="100.3" cy="100" r="100"/>\r
+<circle fill="none" stroke="#FFFFFF" stroke-width="5" stroke-miterlimit="10" cx="100.3" cy="100" r="100"/>\r
+<rect x="47.3" y="47" fill="#FFFFFF" width="106" height="106"/>\r
+</svg>\r