diff options
Diffstat (limited to '1415/fp2')
75 files changed, 9036 insertions, 0 deletions
| diff --git a/1415/fp2/week1/camil/Galgje.icl b/1415/fp2/week1/camil/Galgje.icl new file mode 100644 index 0000000..75b09d0 --- /dev/null +++ b/1415/fp2/week1/camil/Galgje.icl @@ -0,0 +1,58 @@ +// Mart Lubbers s4109503, Camil Staps s4498062
 +
 +module Galgje
 +
 +import StdEnv, SimpleFileIO, RandomGetallen
 +
 +lexicon_file = "lexicon.txt"
 +
 +// Is a Char a member of a String
 +isMemberString :: String Char -> Bool
 +isMemberString "" c = False
 +isMemberString s c = s.[0] == c || isMemberString (s % (1,size s - 1)) c
 +
 +// From the slides
 +skip_nl :: String -> String
 +skip_nl str = if (size str > 0 && str.[size str-1] == '\n') (str%(0,size str-2)) str
 +
 +// From a String and a List of guesses (Chars), return a String that shows dots for letters that were not guessed yet
 +stripUnknown :: String [Char] -> String
 +stripUnknown s g = toString [if (isMember c g) c '.' \\ c <- (fromString s)]
 +
 +// Get a random word from the lexicon file
 +randomWord :: *env -> (Maybe String, *env) | FileSystem env
 +randomWord env
 +# (ss,env) = readLines lexicon_file env
 +| ss == Nothing = (Nothing, env)
 +# (seed,env) = getNewRandomSeed env
 +| otherwise = (Just (skip_nl ((shuffle (fromJust ss) seed)!!0)), env)
 +
 +// word, guesses, mistakes left, stdio -> (win, new guesses, stdio)
 +play :: String [Char] Int *File *env -> (Bool, [Char], *File, *env) | FileSystem env
 +play w g n io world
 +# io = io <<< stripUnknown w g <<< '\n'
 +| stripUnknown w g == w = (True, g, io, world)
 +# (round,world) = readFile ("round-" +++ (toString n) +++ ".txt") world
 +| round == Nothing = abort "Couldn't get gallow"
 +# io = io <<< (fromJust round)
 +# io = io <<< "Guess (" <<< toString n <<< "): "
 +# (ok,g`,io) = freadc io
 +# (_,io) = freadline io // to read until the next \n
 +| not ok = abort "Couldn't get guessed letter"
 +| isMemberString w g` = play w [g`:g] n io world
 +| n == 0 = (False, [g`:g], io, world)
 +| otherwise = play w [g`:g] (n-1) io world
 +
 +Start :: *World -> *World
 +Start world
 +# (word,world) = randomWord world
 +| word == Nothing = abort "Couldn't get random word"
 +# word = fromJust word
 +# (io,world) = stdio world
 +# (win,g,io,world) = play word [] 5 io world
 +# (lost,world) = readFile "round-lost.txt" world
 +| lost == Nothing = abort "Couldn't get gallow"
 +# io = if win (io <<< "You win!\n") (io <<< "You lose!\n" <<< fromJust lost)
 +# (ok,world) = fclose io world
 +| not ok = abort "Couldn't close stdio"
 +| otherwise = world
 diff --git a/1415/fp2/week1/camil/Random.dcl b/1415/fp2/week1/camil/Random.dcl new file mode 100644 index 0000000..47a7c18 --- /dev/null +++ b/1415/fp2/week1/camil/Random.dcl @@ -0,0 +1,19 @@ +definition module Random + + // Random number generator voor Linux gebruikers + // interface compatible met Random.dcl (helaas) + // -- mschool@science.ru.nl + +import StdFile + +:: RandomSeed  + +// nullRandomSeed generates a fixed RandomSeed +nullRandomSeed :: RandomSeed + +// GetNewRandomSeed generates a good RandomSeed, using /dev/urandom +getNewRandomSeed :: !*env -> (!RandomSeed, !*env) | FileSystem env + +// Given a RandomSeed, Random generates a random number and a new RandomSeed. +random :: !RandomSeed -> .(!Int, !RandomSeed) + diff --git a/1415/fp2/week1/camil/Random.icl b/1415/fp2/week1/camil/Random.icl new file mode 100644 index 0000000..b6e0768 --- /dev/null +++ b/1415/fp2/week1/camil/Random.icl @@ -0,0 +1,20 @@ +implementation module Random + +import StdFile, StdList, StdMisc, StdArray, Random + +:: RandomSeed :== Int + +nullRandomSeed :: RandomSeed +nullRandomSeed = 0 + +getNewRandomSeed :: !*env -> (!RandomSeed, !*env) | FileSystem env +getNewRandomSeed env +# (ok, src, env) = sfopen "/dev/urandom" FReadData env +| not ok => abort "could not open /dev/urandom" +# (bytes, src)   = sfreads src 4 +  seed           = foldl (\x y->(x<<8)+toInt y) 0 [c \\ c<-:bytes] +| otherwise => (seed, env) + +random :: !RandomSeed -> .(!Int, !RandomSeed) +random seed = (seed>>16 bitand 0xFFFF, seed*0x08088405+1) + diff --git a/1415/fp2/week1/camil/SimpleFileIO.dcl b/1415/fp2/week1/camil/SimpleFileIO.dcl new file mode 100644 index 0000000..1bd97da --- /dev/null +++ b/1415/fp2/week1/camil/SimpleFileIO.dcl @@ -0,0 +1,14 @@ +definition module SimpleFileIO
 +
 +import StdFile, StdOverloaded, StdMaybe
 +
 +// 1.
 +readFile	:: String                 *env -> (Maybe String,  *env) | FileSystem env
 +writeFile	:: String String          *env -> (Bool,          *env) | FileSystem env
 +
 +// 2.
 +readLines	:: String                 *env -> (Maybe [String],*env) | FileSystem env
 +writeLines	:: String [String]        *env -> (Bool,          *env) | FileSystem env
 +
 +// 3.
 +//mapFile		:: String String (a -> b) *env -> (Bool,          *env) | FileSystem env & ... a & ... b
 diff --git a/1415/fp2/week1/camil/SimpleFileIO.icl b/1415/fp2/week1/camil/SimpleFileIO.icl new file mode 100644 index 0000000..b2a483a --- /dev/null +++ b/1415/fp2/week1/camil/SimpleFileIO.icl @@ -0,0 +1,39 @@ +implementation module SimpleFileIO
 +
 +import StdEnv, StdFile, StdOverloaded, StdMaybe
 +
 +// 1.
 +readFile	:: String                 *env -> (Maybe String,  *env) | FileSystem env
 +readFile s env
 +# (ss, env) = readLines s env
 +| ss == Nothing = (Nothing, env)
 +| otherwise = (Just (foldl (+++) "" (fromJust ss)), env)
 +
 +writeFile	:: String String          *env -> (Bool,          *env) | FileSystem env
 +writeFile fn s env
 +# (ok, outfile, env) = fopen fn FWriteText env
 +| not ok = (False, env)
 +# outfile = fwrites s outfile
 +# (ok, env) = fclose outfile env
 +| otherwise = (ok, env)
 +
 +// 2.
 +readLines	:: String                 *env -> (Maybe [String],*env) | FileSystem env
 +readLines s env
 +# (ok, infile, env) = sfopen s FReadText env
 +| not ok = (Nothing, env)
 +| otherwise = (Just (fst (readLines` infile)), env)
 +where
 +	readLines` :: File -> ([String], File)
 +	readLines` file 
 +	| sfend file = ([], file)
 +	# (line, file) = sfreadline file
 +	# (ss, file) = readLines` file
 +	| otherwise = ([line : ss], file)
 +
 +writeLines	:: String [String]        *env -> (Bool,          *env) | FileSystem env
 +writeLines fn ss env = writeFile fn (foldl (+++) "" [s +++ "\n" \\ s <- ss]) env
 +
 +// 3.
 +//mapFile		:: String String (a -> b) *env -> (Bool,          *env) | FileSystem env & ... a & ... b
 +
 diff --git a/1415/fp2/week1/camil/StdMaybe.dcl b/1415/fp2/week1/camil/StdMaybe.dcl new file mode 100644 index 0000000..2403683 --- /dev/null +++ b/1415/fp2/week1/camil/StdMaybe.dcl @@ -0,0 +1,41 @@ +definition module StdMaybe + +//	******************************************************************************** +//	Clean StdLib library module, version 1.0 +//	******************************************************************************** + +from StdFunc import :: St; +from StdOverloaded import class ==(..); + +::	Maybe x +	=	Just x +	|	Nothing + +isJust		:: !(Maybe .x) -> Bool		// case @1 of (Just _) -> True; _ -> False +isNothing	:: !(Maybe .x) -> Bool		// not o isJust +fromJust	:: !(Maybe .x) -> .x		// \(Just x) -> x + +// for possibly unique elements: +u_isJust :: !u:(Maybe .x) -> (!Bool, !u:Maybe .x) +u_isNothing :: !u:(Maybe .x) -> (!Bool, !u:Maybe .x) + +accMaybe :: .(St .x .a) !u:(Maybe .x) -> (!Maybe .a,!u:Maybe .x) +// accMaybe f (Just x) = (Just (fst (f x)),Just (snd (f x))) +// accMaybe f Nothing  = (Nothing,Nothing) + +mapMaybe	:: .(.x -> .y) !(Maybe .x) -> Maybe .y +// mapMaybe f (Just x) = Just (f x) +// mapMaybe f Nothing  = Nothing + +instance ==       (Maybe x) | == x +//	Nothing==Nothing +//	Just a ==Just b <= a==b + +maybeToList :: !(Maybe .a) -> [.a]; +//	returns list with no or one element + +listToMaybe :: ![.a] -> .Maybe .a; +//	returns Just head of list if possible + +catMaybes :: ![Maybe .a] -> .[.a]; +//	catMaybes ms =  [ m \\ Just m <- ms ] diff --git a/1415/fp2/week1/camil/StdMaybe.icl b/1415/fp2/week1/camil/StdMaybe.icl new file mode 100644 index 0000000..4eed325 --- /dev/null +++ b/1415/fp2/week1/camil/StdMaybe.icl @@ -0,0 +1,65 @@ +implementation module StdMaybe + +//	******************************************************************************** +//	Clean StdLib library module, version 1.0 +//	******************************************************************************** + +from StdFunc import :: St; +from StdOverloaded import class ==(..); + +::	Maybe x +	=	Just x +	|	Nothing + +isJust :: !(Maybe .x) -> Bool +isJust Nothing	= False +isJust _		= True + +isNothing :: !(Maybe .x) -> Bool +isNothing Nothing	= True +isNothing _		= False + +u_isJust :: !u:(Maybe .x) -> (!Bool, !u:Maybe .x) +u_isJust nothing=:Nothing +	= (False, nothing) +u_isJust just +	= (True, just) + +u_isNothing :: !u:(Maybe .x) -> (!Bool, !u:Maybe .x) +u_isNothing nothing=:Nothing +	= (True, nothing) +u_isNothing just +	= (False,just) + +fromJust :: !(Maybe .x) -> .x +fromJust (Just x) = x + +accMaybe :: .(St .x .a) !u:(Maybe .x) -> (!Maybe .a,!u:Maybe .x) +accMaybe f (Just x) +	# (a,x) = f x +	= (Just a,Just x) +accMaybe _ nothing +	= (Nothing,nothing) + +mapMaybe :: .(.x -> .y) !(Maybe .x) -> Maybe .y +mapMaybe f (Just x) = Just (f x) +mapMaybe _ nothing  = Nothing + +instance == (Maybe x) | == x where +	(==) Nothing  maybe	= case maybe of +							Nothing -> True +							just    -> False +	(==) (Just a) maybe	= case maybe of +							Just b  -> a==b +							nothing -> False + +maybeToList :: !(Maybe .a) -> [.a]; +maybeToList Nothing    =  [] +maybeToList (Just a)   =  [a] + +listToMaybe :: ![.a] -> .Maybe .a; +listToMaybe []         =  Nothing +listToMaybe [a:_]      =  Just a +  +catMaybes :: ![Maybe .a] -> .[.a]; +catMaybes ms           =  [ m \\ Just m <- ms ] diff --git a/1415/fp2/week1/camil/lexicon.txt b/1415/fp2/week1/camil/lexicon.txt new file mode 100644 index 0000000..9c2ad4e --- /dev/null +++ b/1415/fp2/week1/camil/lexicon.txt @@ -0,0 +1,18 @@ +armada +balinese +bergens +cyprus +europeanen +guldensporenslag +hollandermop +jordaans +lagerhuis +luiker +mensenzoon +opperwezen +randstad +samaritaan +sovjettijd +thailand +vietnamese +zeeuws diff --git a/1415/fp2/week1/camil/round-0.txt b/1415/fp2/week1/camil/round-0.txt new file mode 100644 index 0000000..7236e17 --- /dev/null +++ b/1415/fp2/week1/camil/round-0.txt @@ -0,0 +1,7 @@ +  ------ +  |  \ | +  o   \| + /O\   | +       | +       | +________ diff --git a/1415/fp2/week1/camil/round-1.txt b/1415/fp2/week1/camil/round-1.txt new file mode 100644 index 0000000..8694aad --- /dev/null +++ b/1415/fp2/week1/camil/round-1.txt @@ -0,0 +1,7 @@ +  ------ +  |  \ | +  o   \| +       | +       | +       | +________ diff --git a/1415/fp2/week1/camil/round-2.txt b/1415/fp2/week1/camil/round-2.txt new file mode 100644 index 0000000..d46d77c --- /dev/null +++ b/1415/fp2/week1/camil/round-2.txt @@ -0,0 +1,7 @@ +  ------ +  |  \ | +      \| +       | +       | +       | +________ diff --git a/1415/fp2/week1/camil/round-3.txt b/1415/fp2/week1/camil/round-3.txt new file mode 100644 index 0000000..9bdd2ba --- /dev/null +++ b/1415/fp2/week1/camil/round-3.txt @@ -0,0 +1,7 @@ +  ------ +     \ | +      \| +       | +       | +       | +________ diff --git a/1415/fp2/week1/camil/round-4.txt b/1415/fp2/week1/camil/round-4.txt new file mode 100644 index 0000000..41ca216 --- /dev/null +++ b/1415/fp2/week1/camil/round-4.txt @@ -0,0 +1,7 @@ + +       | +       | +       | +       | +       | +________ diff --git a/1415/fp2/week1/camil/round-5.txt b/1415/fp2/week1/camil/round-5.txt new file mode 100644 index 0000000..f29c0dd --- /dev/null +++ b/1415/fp2/week1/camil/round-5.txt @@ -0,0 +1,7 @@ + + + + + + +________ diff --git a/1415/fp2/week1/camil/round-lost.txt b/1415/fp2/week1/camil/round-lost.txt new file mode 100644 index 0000000..7ec2fa7 --- /dev/null +++ b/1415/fp2/week1/camil/round-lost.txt @@ -0,0 +1,7 @@ +  ------ +  |  \ | +  o   \| + /O\   | + / \   | +       | +________ diff --git a/1415/fp2/week1/camil/week1.tar.gz b/1415/fp2/week1/camil/week1.tar.gzBinary files differ new file mode 100644 index 0000000..3533265 --- /dev/null +++ b/1415/fp2/week1/camil/week1.tar.gz diff --git a/1415/fp2/week1/mart/Echo b/1415/fp2/week1/mart/EchoBinary files differ new file mode 100755 index 0000000..cf2fb79 --- /dev/null +++ b/1415/fp2/week1/mart/Echo diff --git a/1415/fp2/week1/mart/Echo.icl b/1415/fp2/week1/mart/Echo.icl new file mode 100644 index 0000000..30a6f4b --- /dev/null +++ b/1415/fp2/week1/mart/Echo.icl @@ -0,0 +1,11 @@ +module Echo
 +
 +import StdEnv
 +
 +
 +Start :: *World -> *World
 +Start world
 +# (console, world) = stdio world
 +# (line, console) = freadline console
 +| not (fend console) = fwrites line
 +| otherwise = world
 diff --git a/1415/fp2/week1/mart/Galgje b/1415/fp2/week1/mart/GalgjeBinary files differ new file mode 100755 index 0000000..d46de77 --- /dev/null +++ b/1415/fp2/week1/mart/Galgje diff --git a/1415/fp2/week1/mart/Galgje.icl b/1415/fp2/week1/mart/Galgje.icl new file mode 100644 index 0000000..e5106ee --- /dev/null +++ b/1415/fp2/week1/mart/Galgje.icl @@ -0,0 +1,13 @@ +module Galgje
 +
 +import StdEnv, Random
 +
 +//randomWord :: *env -> (Maybe String, *env) | FileSystem env                     
 +//randomWord env                                                                  
 +//# (ss,env) = readLines lexicon_file env                                         
 +//| ss == Nothing = (Nothing, env)                                                
 +//# (seed,env) = getNewRandomSeed env                                             
 +//| otherwise = (Just (skip_nl ((shuffle (fromJust ss) seed)!!0)), env) 
 +
 +Start :: *World -> *World
 +Start world = world
 diff --git a/1415/fp2/week1/mart/GalgjeWF.dcl b/1415/fp2/week1/mart/GalgjeWF.dcl new file mode 100644 index 0000000..a777b95 --- /dev/null +++ b/1415/fp2/week1/mart/GalgjeWF.dcl @@ -0,0 +1,5 @@ +definition module GalgjeWF
 +
 +import iTasks
 +
 +galgje :: [Workflow]
 diff --git a/1415/fp2/week1/mart/Random.dcl b/1415/fp2/week1/mart/Random.dcl new file mode 100644 index 0000000..47a7c18 --- /dev/null +++ b/1415/fp2/week1/mart/Random.dcl @@ -0,0 +1,19 @@ +definition module Random + + // Random number generator voor Linux gebruikers + // interface compatible met Random.dcl (helaas) + // -- mschool@science.ru.nl + +import StdFile + +:: RandomSeed  + +// nullRandomSeed generates a fixed RandomSeed +nullRandomSeed :: RandomSeed + +// GetNewRandomSeed generates a good RandomSeed, using /dev/urandom +getNewRandomSeed :: !*env -> (!RandomSeed, !*env) | FileSystem env + +// Given a RandomSeed, Random generates a random number and a new RandomSeed. +random :: !RandomSeed -> .(!Int, !RandomSeed) + diff --git a/1415/fp2/week1/mart/Random.icl b/1415/fp2/week1/mart/Random.icl new file mode 100644 index 0000000..b6e0768 --- /dev/null +++ b/1415/fp2/week1/mart/Random.icl @@ -0,0 +1,20 @@ +implementation module Random + +import StdFile, StdList, StdMisc, StdArray, Random + +:: RandomSeed :== Int + +nullRandomSeed :: RandomSeed +nullRandomSeed = 0 + +getNewRandomSeed :: !*env -> (!RandomSeed, !*env) | FileSystem env +getNewRandomSeed env +# (ok, src, env) = sfopen "/dev/urandom" FReadData env +| not ok => abort "could not open /dev/urandom" +# (bytes, src)   = sfreads src 4 +  seed           = foldl (\x y->(x<<8)+toInt y) 0 [c \\ c<-:bytes] +| otherwise => (seed, env) + +random :: !RandomSeed -> .(!Int, !RandomSeed) +random seed = (seed>>16 bitand 0xFFFF, seed*0x08088405+1) + diff --git a/1415/fp2/week1/mart/RandomGetallen b/1415/fp2/week1/mart/RandomGetallenBinary files differ new file mode 100755 index 0000000..0482437 --- /dev/null +++ b/1415/fp2/week1/mart/RandomGetallen diff --git a/1415/fp2/week1/mart/RandomGetallen.dcl b/1415/fp2/week1/mart/RandomGetallen.dcl new file mode 100644 index 0000000..66a2c6c --- /dev/null +++ b/1415/fp2/week1/mart/RandomGetallen.dcl @@ -0,0 +1,7 @@ +definition module RandomGetallen
 +
 +import Random
 +
 +random_n	:: Int RandomSeed -> ([Int],RandomSeed)
 +random_inf	::     RandomSeed ->  [Int]
 +//shuffle		:: [a] RandomSeed ->  [a]
 diff --git a/1415/fp2/week1/mart/RandomGetallen.icl b/1415/fp2/week1/mart/RandomGetallen.icl new file mode 100644 index 0000000..b756c91 --- /dev/null +++ b/1415/fp2/week1/mart/RandomGetallen.icl @@ -0,0 +1,33 @@ +implementation module RandomGetallen
 +
 +import StdEnv, Random
 +
 +//Start :: *World -> ([Int],*World)
 +//Start world
 +//# (rs,world)	= getNewRandomSeed world
 +//= (shuffle [1..10] rs,world)
 +
 +
 +Start = shuffle [1..10] nullRandomSeed
 +
 +random_n :: Int RandomSeed -> ([Int],RandomSeed)
 +random_n n seed = seqList (repeatn n random) seed
 +
 +random_inf :: RandomSeed -> [Int]
 +random_inf seed = iterateSt random seed
 +
 +iterateSt :: (s -> (a,s)) s -> [a]
 +iterateSt f s = [a : iterateSt f s`]
 +where
 +	(a,s`) = f s
 +
 +shuffle :: [a] RandomSeed -> [a]
 +shuffle xs seed = (perms xs) !! ((fst (random seed)) rem (fac (length xs)))
 +
 +fac :: Int -> Int
 +fac 0 = 1
 +fac n = n * fac (n-1)
 +
 +perms :: [a] -> [[a]]
 +perms [] = [[]]
 +perms xs = [[xs!!i : xs`] \\ i <- [0..length xs - 1] , xs` <- perms (take i xs ++ drop (i+1) xs)]
 diff --git a/1415/fp2/week1/mart/SimpleFileIO.dcl b/1415/fp2/week1/mart/SimpleFileIO.dcl new file mode 100644 index 0000000..1bd97da --- /dev/null +++ b/1415/fp2/week1/mart/SimpleFileIO.dcl @@ -0,0 +1,14 @@ +definition module SimpleFileIO
 +
 +import StdFile, StdOverloaded, StdMaybe
 +
 +// 1.
 +readFile	:: String                 *env -> (Maybe String,  *env) | FileSystem env
 +writeFile	:: String String          *env -> (Bool,          *env) | FileSystem env
 +
 +// 2.
 +readLines	:: String                 *env -> (Maybe [String],*env) | FileSystem env
 +writeLines	:: String [String]        *env -> (Bool,          *env) | FileSystem env
 +
 +// 3.
 +//mapFile		:: String String (a -> b) *env -> (Bool,          *env) | FileSystem env & ... a & ... b
 diff --git a/1415/fp2/week1/mart/SimpleFileIO.icl b/1415/fp2/week1/mart/SimpleFileIO.icl new file mode 100644 index 0000000..b2a483a --- /dev/null +++ b/1415/fp2/week1/mart/SimpleFileIO.icl @@ -0,0 +1,39 @@ +implementation module SimpleFileIO
 +
 +import StdEnv, StdFile, StdOverloaded, StdMaybe
 +
 +// 1.
 +readFile	:: String                 *env -> (Maybe String,  *env) | FileSystem env
 +readFile s env
 +# (ss, env) = readLines s env
 +| ss == Nothing = (Nothing, env)
 +| otherwise = (Just (foldl (+++) "" (fromJust ss)), env)
 +
 +writeFile	:: String String          *env -> (Bool,          *env) | FileSystem env
 +writeFile fn s env
 +# (ok, outfile, env) = fopen fn FWriteText env
 +| not ok = (False, env)
 +# outfile = fwrites s outfile
 +# (ok, env) = fclose outfile env
 +| otherwise = (ok, env)
 +
 +// 2.
 +readLines	:: String                 *env -> (Maybe [String],*env) | FileSystem env
 +readLines s env
 +# (ok, infile, env) = sfopen s FReadText env
 +| not ok = (Nothing, env)
 +| otherwise = (Just (fst (readLines` infile)), env)
 +where
 +	readLines` :: File -> ([String], File)
 +	readLines` file 
 +	| sfend file = ([], file)
 +	# (line, file) = sfreadline file
 +	# (ss, file) = readLines` file
 +	| otherwise = ([line : ss], file)
 +
 +writeLines	:: String [String]        *env -> (Bool,          *env) | FileSystem env
 +writeLines fn ss env = writeFile fn (foldl (+++) "" [s +++ "\n" \\ s <- ss]) env
 +
 +// 3.
 +//mapFile		:: String String (a -> b) *env -> (Bool,          *env) | FileSystem env & ... a & ... b
 +
 diff --git a/1415/fp2/week2/camil/StdIOMonad.dcl b/1415/fp2/week2/camil/StdIOMonad.dcl new file mode 100644 index 0000000..580efaa --- /dev/null +++ b/1415/fp2/week2/camil/StdIOMonad.dcl @@ -0,0 +1,40 @@ +definition module StdIOMonad
 +
 +//	Deze module verpakt een aantal StdFile functies in een monadische jas
 +
 +import StdMonad, StdMaybe
 +
 +:: IO a
 +:: *W
 +:: Void       = Void
 +:: Filemode   = Lees | Schrijf
 +:: Filenaam :== String
 +:: Filehandle :== String
 +
 +//	voer monadische I/O actie uit op de wereld:
 +doIO:: (IO a) *World -> *(a, *W)
 +
 +//  IO is een monad:
 +instance return IO
 +instance >>=    IO
 +
 +//	lees regel van de console:
 +read		:: IO String
 +
 +//	schrijf regel naar de console:
 +write		:: String -> IO Void
 +
 +//	open de file met gegeven filenaam en mode:
 +open		:: Filenaam Filemode -> IO (Maybe Filehandle)
 +
 +//	sluit de file met gegeven filenaam:
 +close		:: Filehandle -> IO Bool
 +
 +//	bepaal of het lezen van de file klaar is:
 +eof			:: Filehandle -> IO Bool
 +
 +//	lees een regel van een file:
 +readline	:: Filehandle -> IO (Maybe String)
 +
 +//	schrijf een regel naar een file:
 +writeline	:: String Filehandle -> IO Bool
 diff --git a/1415/fp2/week2/camil/StdIOMonad.icl b/1415/fp2/week2/camil/StdIOMonad.icl new file mode 100644 index 0000000..c25cb4c --- /dev/null +++ b/1415/fp2/week2/camil/StdIOMonad.icl @@ -0,0 +1,130 @@ +implementation module StdIOMonad
 +
 +import StdBool
 +import StdEnum
 +import StdFile
 +import StdList
 +import StdMaybe
 +import StdMisc
 +import StdMonad
 +import StdOverloaded
 +import StdString
 +import StdTuple
 +
 +:: IO a = IO (*W -> *(a, *W))
 +:: *W :== *(*World, *[*(Filehandle, *File)])
 +:: Filemode = Lees | Schrijf
 +:: Filenaam :== String
 +:: Filehandle :== String
 +
 +instance toInt Filemode where
 +	toInt Lees = FReadText
 +	toInt Schrijf = FWriteText
 +
 +//voer monadische I/O actie uit op de wereld:
 +doIO:: (IO a) *World -> *(a, *W)
 +doIO (IO f) w = f (w, [])
 +
 +unIO:: (IO a) -> *W -> *(a, *W)
 +unIO (IO f) = f 
 +
 +//  IO is een monad:
 +instance return IO where
 +	return x = IO (\w -> (x, w))
 +instance >>=    IO where
 +	(>>=) (IO f) g = IO (\w = let (a, w1) = f w in unIO (g a) w1)
 +
 +read:: IO String
 +read = IO read`
 +	where
 +		read`:: *W -> *(String, *W)
 +		read` (world, s)
 +		# (io, world) = stdio world
 +		# (line, io) = freadline io
 +		# (_, world) = fclose io world
 +		= (line, (world, s))
 +
 +//	schrijf regel naar de console:
 +write		:: String -> IO Void
 +write s = IO (write` s)
 +	where
 +		write`:: String *W -> *(Void, *W)
 +		write` line (world, s)
 +		# (io, world) = stdio world
 +		# io = io <<< line
 +		# (_, world) = fclose io world
 +		= (Void, (world, s))
 +
 +//	open de file met gegeven filenaam en mode:
 +find:: Filehandle *[*(Filehandle, *File)] -> (Maybe *(Filehandle, *File), *[*(Filehandle, *File)]) 
 +find fh fs
 +# (fhs, fis) = unzip fs
 +# fhsC = zip2 [0..length fhs] fhs
 +# index = [(i, h) \\ (i, h) <- fhsC | h == fh]
 +| length index == 0 = (Nothing, zip2 fhs fis)
 +# index = fst (hd index)
 +# (fis1, fis2) = splitAt index fis
 +# (fhs1, fhs2) = splitAt index fhs
 +# (thefile, fis2) = splitAt 1 fis2
 +# (thehandle, fhs2) = splitAt 1 fhs2
 += (Just (hd thehandle, hd thefile), zip2 (fhs1 ++ fhs2) (fis1 ++ fis2))
 +
 +
 +open:: Filenaam Filemode -> IO (Maybe Filehandle)
 +open s m = IO (open` s m)
 +	where
 +		open`:: String Filemode *W -> *(Maybe Filehandle, *W)
 +		open` fp m (world, fs)
 +		| any (\l = fp == fst l) fs = (Nothing, (world, fs))
 +		# (ok, file, world) = fopen fp (toInt m) world
 +		= (Just fp, (world, [(fp, file):fs]))
 +
 +//	sluit de file met gegeven filenaam:
 +close:: Filehandle -> IO Bool
 +close fh = IO (close` fh)
 +	where
 +		close`:: Filehandle *W -> *(Bool, *W)
 +		close` fp (world, fs)
 +		# (currentfiletuple, fs) = find fp fs
 +		| isNothing currentfiletuple = (False, (world, fs))
 +		# (currentfh, currentfile) = fromJust currentfiletuple
 +		# (ok, world) = fclose currentfile world
 +		| not ok = abort "File can't be closed"
 +		| otherwise = (True, (world, fs))
 +		
 +
 +//	bepaal of het lezen van de file klaar is:
 +eof			:: Filehandle -> IO Bool
 +eof fh = IO (eof` fh)
 +	where 
 +		eof`:: Filehandle *W -> *(Bool, *W)
 +		eof` fp (world, fs)
 +		# (currentfiletuple, fs) = find fp fs
 +		| isNothing currentfiletuple = abort "Can't do eof on non-existing file"
 +		# (currentfh, currentfile) = fromJust currentfiletuple
 +		# (ok, file) = fend currentfile
 +		= (ok, (world, [(currentfh, file):fs]))
 +
 +//	lees een regel van een file:
 +readline	:: Filehandle -> IO (Maybe String)
 +readline fh = IO (readline` fh)
 +	where
 +		readline` :: Filehandle *W -> *(Maybe String, *W)
 +		readline` fh (world, fs)
 +		# (currentfiletuple, fs) = find fh fs
 +		| isNothing currentfiletuple = (Nothing, (world, fs))
 +		# (currentfh, currentfile) = fromJust currentfiletuple
 +		# (s, currentfile) = freadline currentfile
 +		= (Just s, (world, [(currentfh, currentfile):fs]))
 +
 +//	schrijf een regel naar een file:
 +writeline	:: String Filehandle -> IO Bool
 +writeline s fh = IO (writeline` s fh)
 +	where
 +		writeline` :: String Filehandle *W -> *(Bool, *W)
 +		writeline` s fh (world, fs)
 +		# (currentfiletuple, fs) = find fh fs
 +		| isNothing currentfiletuple = (True, (world, fs))
 +		# (currentfh, currentfile) = fromJust currentfiletuple
 +		# currentfile = fwrites (s +++ "\n") currentfile
 +		= (True, (world, [(currentfh, currentfile):fs]))
 diff --git a/1415/fp2/week2/camil/StdMaybe.dcl b/1415/fp2/week2/camil/StdMaybe.dcl new file mode 100644 index 0000000..2403683 --- /dev/null +++ b/1415/fp2/week2/camil/StdMaybe.dcl @@ -0,0 +1,41 @@ +definition module StdMaybe + +//	******************************************************************************** +//	Clean StdLib library module, version 1.0 +//	******************************************************************************** + +from StdFunc import :: St; +from StdOverloaded import class ==(..); + +::	Maybe x +	=	Just x +	|	Nothing + +isJust		:: !(Maybe .x) -> Bool		// case @1 of (Just _) -> True; _ -> False +isNothing	:: !(Maybe .x) -> Bool		// not o isJust +fromJust	:: !(Maybe .x) -> .x		// \(Just x) -> x + +// for possibly unique elements: +u_isJust :: !u:(Maybe .x) -> (!Bool, !u:Maybe .x) +u_isNothing :: !u:(Maybe .x) -> (!Bool, !u:Maybe .x) + +accMaybe :: .(St .x .a) !u:(Maybe .x) -> (!Maybe .a,!u:Maybe .x) +// accMaybe f (Just x) = (Just (fst (f x)),Just (snd (f x))) +// accMaybe f Nothing  = (Nothing,Nothing) + +mapMaybe	:: .(.x -> .y) !(Maybe .x) -> Maybe .y +// mapMaybe f (Just x) = Just (f x) +// mapMaybe f Nothing  = Nothing + +instance ==       (Maybe x) | == x +//	Nothing==Nothing +//	Just a ==Just b <= a==b + +maybeToList :: !(Maybe .a) -> [.a]; +//	returns list with no or one element + +listToMaybe :: ![.a] -> .Maybe .a; +//	returns Just head of list if possible + +catMaybes :: ![Maybe .a] -> .[.a]; +//	catMaybes ms =  [ m \\ Just m <- ms ] diff --git a/1415/fp2/week2/camil/StdMaybe.icl b/1415/fp2/week2/camil/StdMaybe.icl new file mode 100644 index 0000000..4eed325 --- /dev/null +++ b/1415/fp2/week2/camil/StdMaybe.icl @@ -0,0 +1,65 @@ +implementation module StdMaybe + +//	******************************************************************************** +//	Clean StdLib library module, version 1.0 +//	******************************************************************************** + +from StdFunc import :: St; +from StdOverloaded import class ==(..); + +::	Maybe x +	=	Just x +	|	Nothing + +isJust :: !(Maybe .x) -> Bool +isJust Nothing	= False +isJust _		= True + +isNothing :: !(Maybe .x) -> Bool +isNothing Nothing	= True +isNothing _		= False + +u_isJust :: !u:(Maybe .x) -> (!Bool, !u:Maybe .x) +u_isJust nothing=:Nothing +	= (False, nothing) +u_isJust just +	= (True, just) + +u_isNothing :: !u:(Maybe .x) -> (!Bool, !u:Maybe .x) +u_isNothing nothing=:Nothing +	= (True, nothing) +u_isNothing just +	= (False,just) + +fromJust :: !(Maybe .x) -> .x +fromJust (Just x) = x + +accMaybe :: .(St .x .a) !u:(Maybe .x) -> (!Maybe .a,!u:Maybe .x) +accMaybe f (Just x) +	# (a,x) = f x +	= (Just a,Just x) +accMaybe _ nothing +	= (Nothing,nothing) + +mapMaybe :: .(.x -> .y) !(Maybe .x) -> Maybe .y +mapMaybe f (Just x) = Just (f x) +mapMaybe _ nothing  = Nothing + +instance == (Maybe x) | == x where +	(==) Nothing  maybe	= case maybe of +							Nothing -> True +							just    -> False +	(==) (Just a) maybe	= case maybe of +							Just b  -> a==b +							nothing -> False + +maybeToList :: !(Maybe .a) -> [.a]; +maybeToList Nothing    =  [] +maybeToList (Just a)   =  [a] + +listToMaybe :: ![.a] -> .Maybe .a; +listToMaybe []         =  Nothing +listToMaybe [a:_]      =  Just a +  +catMaybes :: ![Maybe .a] -> .[.a]; +catMaybes ms           =  [ m \\ Just m <- ms ] diff --git a/1415/fp2/week2/camil/StdMonad.dcl b/1415/fp2/week2/camil/StdMonad.dcl new file mode 100644 index 0000000..cd1c654 --- /dev/null +++ b/1415/fp2/week2/camil/StdMonad.dcl @@ -0,0 +1,8 @@ +definition module StdMonad
 +
 +class return        c :: a -> c a
 +class (>>=) infix 0	c :: (c a) (a -> c b) -> c b
 +class fail          c :: c a
 +
 +class Monad	        c | return, >>= c
 +class MonadFail	    c | Monad, fail c
 diff --git a/1415/fp2/week2/camil/StdMonad.icl b/1415/fp2/week2/camil/StdMonad.icl new file mode 100644 index 0000000..db193ab --- /dev/null +++ b/1415/fp2/week2/camil/StdMonad.icl @@ -0,0 +1 @@ +implementation module StdMonad
 diff --git a/1415/fp2/week2/camil/Test.dcl b/1415/fp2/week2/camil/Test.dcl new file mode 100644 index 0000000..21f08d1 --- /dev/null +++ b/1415/fp2/week2/camil/Test.dcl @@ -0,0 +1 @@ +definition module Test diff --git a/1415/fp2/week2/camil/Test.icl b/1415/fp2/week2/camil/Test.icl new file mode 100644 index 0000000..8044d3f --- /dev/null +++ b/1415/fp2/week2/camil/Test.icl @@ -0,0 +1,12 @@ +implementation module Test
 +
 +import StdIOMonad
 +
 +Start world = doIO (
 +	open "camil.txt" Lees >>=
 +	\_ = open "mart.txt" Schrijf >>=
 +	\_ = readline "camil.txt" >>=
 +	\l = writeline (fromJust l) "mart.txt" >>=
 +	\_ = close "camil.txt" >>=
 +	\_ = close "mart.txt"
 +	) world
 diff --git a/1415/fp2/week2/mart/StdIOMonad.dcl b/1415/fp2/week2/mart/StdIOMonad.dcl new file mode 100644 index 0000000..580efaa --- /dev/null +++ b/1415/fp2/week2/mart/StdIOMonad.dcl @@ -0,0 +1,40 @@ +definition module StdIOMonad
 +
 +//	Deze module verpakt een aantal StdFile functies in een monadische jas
 +
 +import StdMonad, StdMaybe
 +
 +:: IO a
 +:: *W
 +:: Void       = Void
 +:: Filemode   = Lees | Schrijf
 +:: Filenaam :== String
 +:: Filehandle :== String
 +
 +//	voer monadische I/O actie uit op de wereld:
 +doIO:: (IO a) *World -> *(a, *W)
 +
 +//  IO is een monad:
 +instance return IO
 +instance >>=    IO
 +
 +//	lees regel van de console:
 +read		:: IO String
 +
 +//	schrijf regel naar de console:
 +write		:: String -> IO Void
 +
 +//	open de file met gegeven filenaam en mode:
 +open		:: Filenaam Filemode -> IO (Maybe Filehandle)
 +
 +//	sluit de file met gegeven filenaam:
 +close		:: Filehandle -> IO Bool
 +
 +//	bepaal of het lezen van de file klaar is:
 +eof			:: Filehandle -> IO Bool
 +
 +//	lees een regel van een file:
 +readline	:: Filehandle -> IO (Maybe String)
 +
 +//	schrijf een regel naar een file:
 +writeline	:: String Filehandle -> IO Bool
 diff --git a/1415/fp2/week2/mart/StdIOMonad.icl b/1415/fp2/week2/mart/StdIOMonad.icl new file mode 100644 index 0000000..ffa2857 --- /dev/null +++ b/1415/fp2/week2/mart/StdIOMonad.icl @@ -0,0 +1,138 @@ +implementation module StdIOMonad
 +
 +import StdBool
 +import StdEnum
 +import StdFile
 +import StdList
 +import StdMaybe
 +import StdMisc
 +import StdMonad
 +import StdOverloaded
 +import StdString
 +import StdTuple
 +
 +:: IO a = IO (*W -> *(a, *W))
 +:: *W :== *(*World, *[*(Filehandle, *File)])
 +:: Filemode = Lees | Schrijf
 +:: Filenaam :== String
 +:: Filehandle :== String
 +
 +// Conversion from our filemodes to StdFile filemodes
 +instance toInt Filemode where
 +	toInt Lees = FReadText
 +	toInt Schrijf = FWriteText
 +
 +// Apply the monadic program on the world
 +doIO:: (IO a) *World -> *(a, *W)
 +doIO (IO f) w = f (w, [])
 +
 +// Lift the value out of the monadic domain
 +unIO:: (IO a) -> *W -> *(a, *W)
 +unIO (IO f) = f 
 +
 +instance return IO where
 +	return x = IO (\w -> (x, w))
 +instance >>=    IO where
 +	(>>=) (IO f) g = IO (\w = let (a, w1) = f w in unIO (g a) w1)
 +
 +// Read one line from the console
 +read:: IO String
 +read = IO read`
 +	where
 +		read`:: *W -> *(String, *W)
 +		read` (world, s)
 +		# (io, world) = stdio world
 +		# (line, io) = freadline io
 +		# (_, world) = fclose io world
 +		= (line, (world, s))
 +
 +// Write a line from the console
 +write		:: String -> IO Void
 +write s = IO (write` s)
 +	where
 +		write`:: String *W -> *(Void, *W)
 +		write` line (world, s)
 +		# (io, world) = stdio world
 +		# io = io <<< line
 +		# (_, world) = fclose io world
 +		= (Void, (world, s))
 +
 +// Open a file
 +open:: Filenaam Filemode -> IO (Maybe Filehandle)
 +open s m = IO (open` s m)
 +	where
 +		open`:: String Filemode *W -> *(Maybe Filehandle, *W)
 +		open` fp m (world, fs)
 +		| any (\l = fp == fst l) fs = (Nothing, (world, fs))
 +		# (ok, file, world) = fopen fp (toInt m) world
 +		= (Just fp, (world, [(fp, file):fs]))
 +
 +// Close a file. If the file can't be closed by the system the program will
 +// abort
 +close:: Filehandle -> IO Bool
 +close fh = IO (close` fh)
 +	where
 +		close`:: Filehandle *W -> *(Bool, *W)
 +		close` fp (world, fs)
 +		# (currentfiletuple, fs) = getFH fp fs
 +		| isNothing currentfiletuple = (False, (world, fs))
 +		# (currentfh, currentfile) = fromJust currentfiletuple
 +		# (ok, world) = fclose currentfile world
 +		| not ok = abort "File can't be closed"
 +		| otherwise = (True, (world, fs))
 +		
 +
 +// Determine if the file is at the end. This will abort when the file is not
 +// open or error if the file is not opened for reading.
 +eof			:: Filehandle -> IO Bool
 +eof fh = IO (eof` fh)
 +	where 
 +		eof`:: Filehandle *W -> *(Bool, *W)
 +		eof` fp (world, fs)
 +		# (currentfiletuple, fs) = getFH fp fs
 +		| isNothing currentfiletuple = abort "Can't do eof on non-existing file"
 +		# (currentfh, currentfile) = fromJust currentfiletuple
 +		# (ok, file) = fend currentfile
 +		= (ok, (world, [(currentfh, file):fs]))
 +
 +// Read one line from a file (including newline). This will abort when the file
 +// is not open or error if the file is not opened for reading.
 +readline	:: Filehandle -> IO (Maybe String)
 +readline fh = IO (readline` fh)
 +	where
 +		readline` :: Filehandle *W -> *(Maybe String, *W)
 +		readline` fh (world, fs)
 +		# (currentfiletuple, fs) = getFH fh fs
 +		| isNothing currentfiletuple = abort "File not open"
 +		# (currentfh, currentfile) = fromJust currentfiletuple
 +		# (s, currentfile) = freadline currentfile
 +		= (Just s, (world, [(currentfh, currentfile):fs]))
 +
 +// Write one line from a file (will not append newline). This will abort when
 +// the file is not open or error if the file is not opened for writing.
 +writeline	:: String Filehandle -> IO Bool
 +writeline s fh = IO (writeline` s fh)
 +	where
 +		writeline` :: String Filehandle *W -> *(Bool, *W)
 +		writeline` s fh (world, fs)
 +		# (currentfiletuple, fs) = getFH fh fs
 +		| isNothing currentfiletuple = abort "File not open"
 +		# (currentfh, currentfile) = fromJust currentfiletuple
 +		# currentfile = fwrites s currentfile
 +		= (True, (world, [(currentfh, currentfile):fs]))
 +
 +// Gets the file associated with the filehandle given, this is done in a very
 +// ugly way to retain uniqueness...
 +getFH:: Filehandle *[*(Filehandle, *File)] ->
 +	(Maybe *(Filehandle, *File), *[*(Filehandle, *File)]) 
 +getFH fh fs
 +# (fhs, fis) = unzip fs
 +# fhsC = zip2 [0..length fhs] fhs
 +# index = [(i, h) \\ (i, h) <- fhsC | h == fh]
 +| length index == 0 = (Nothing, zip2 fhs fis)
 +# index = fst (hd index)
 +# (fis1, fis2) = splitAt index fis
 +# (fhs1, fhs2) = splitAt index fhs
 +# (thefile, fis2) = splitAt 1 fis2
 +# (thehandle, fhs2) = splitAt 1 fhs2
 += (Just (hd thehandle, hd thefile), zip2 (fhs1 ++ fhs2) (fis1 ++ fis2))
 diff --git a/1415/fp2/week2/mart/StdMonad.dcl b/1415/fp2/week2/mart/StdMonad.dcl new file mode 100644 index 0000000..cd1c654 --- /dev/null +++ b/1415/fp2/week2/mart/StdMonad.dcl @@ -0,0 +1,8 @@ +definition module StdMonad
 +
 +class return        c :: a -> c a
 +class (>>=) infix 0	c :: (c a) (a -> c b) -> c b
 +class fail          c :: c a
 +
 +class Monad	        c | return, >>= c
 +class MonadFail	    c | Monad, fail c
 diff --git a/1415/fp2/week2/mart/StdMonad.icl b/1415/fp2/week2/mart/StdMonad.icl new file mode 100644 index 0000000..db193ab --- /dev/null +++ b/1415/fp2/week2/mart/StdMonad.icl @@ -0,0 +1 @@ +implementation module StdMonad
 diff --git a/1415/fp2/week2/mart/Test.dcl b/1415/fp2/week2/mart/Test.dcl new file mode 100644 index 0000000..21f08d1 --- /dev/null +++ b/1415/fp2/week2/mart/Test.dcl @@ -0,0 +1 @@ +definition module Test diff --git a/1415/fp2/week2/mart/Test.icl b/1415/fp2/week2/mart/Test.icl new file mode 100644 index 0000000..ff32dfe --- /dev/null +++ b/1415/fp2/week2/mart/Test.icl @@ -0,0 +1,13 @@ +implementation module Test
 +
 +import StdIOMonad
 +
 +// This assumes a file "camil.txt" and writes a line from it to "mart.txt"
 +Start world = doIO (
 +	open "camil.txt" Lees >>=
 +	\_ = open "mart.txt" Schrijf >>=
 +	\_ = readline "camil.txt" >>=
 +	\l = writeline (fromJust l) "mart.txt" >>=
 +	\_ = close "camil.txt" >>=
 +	\_ = close "mart.txt"
 +	) world
 diff --git a/1415/fp2/week2/mart/camil.txt b/1415/fp2/week2/mart/camil.txt new file mode 100644 index 0000000..b8b933b --- /dev/null +++ b/1415/fp2/week2/mart/camil.txt @@ -0,0 +1,2 @@ +Line one +Line two diff --git a/1415/fp2/week2/mart/s4109503_s4498062_fp2_w2.tar.gz b/1415/fp2/week2/mart/s4109503_s4498062_fp2_w2.tar.gzBinary files differ new file mode 100644 index 0000000..587d742 --- /dev/null +++ b/1415/fp2/week2/mart/s4109503_s4498062_fp2_w2.tar.gz diff --git a/1415/fp2/week3/camil/StdDynSet.dcl b/1415/fp2/week3/camil/StdDynSet.dcl new file mode 100644 index 0000000..160af6c --- /dev/null +++ b/1415/fp2/week3/camil/StdDynSet.dcl @@ -0,0 +1,24 @@ +definition module StdDynSet + +import StdOverloaded + +class Set a | TC, ==, toString a + +:: Set + +instance zero     Set +instance toString Set +instance ==       Set + +toSet			:: a       -> Set  | Set a + +nrOfElts		::     Set -> Int +isEmptySet		::     Set -> Bool + +memberOfSet		:: a   Set -> Bool | Set a +isSubset		:: Set Set -> Bool +isStrictSubset	:: Set Set -> Bool + +union			:: Set Set -> Set +intersection	:: Set Set -> Set +without			:: Set Set -> Set diff --git a/1415/fp2/week3/camil/StdDynSet.icl b/1415/fp2/week3/camil/StdDynSet.icl new file mode 100644 index 0000000..576bec9 --- /dev/null +++ b/1415/fp2/week3/camil/StdDynSet.icl @@ -0,0 +1,62 @@ +// Mart Lubbers s4109503, Camil Staps s4498062 + +implementation module StdDynSet + +import StdEnv +import StdMaybe +import StdDynamic + +isEqual:: Dynamic t -> Bool | Set t +isEqual (x :: t^) a = x == a +isEqual _ _ = False + +class Set a | TC, ==, toString a + +:: Set = Set [(Dynamic, Dynamic -> Bool, String)] + +instance zero     Set +where zero = Set [] + +instance toString Set +where toString (Set [(_,_,a):as]) = "{" +++ a +++ (foldl (+++) "" ["," +++ s \\ (_,_,s) <- as]) +++ "}" +	 +instance == Set +where == a b = nrOfElts a == nrOfElts b && isSubset a b + +toSet :: a -> Set | Set a +toSet e = Set [(dynamic e, \x = isEqual x e, toString e)] + +nrOfElts :: Set -> Int +nrOfElts (Set a) = length a + +isEmptySet :: Set -> Bool +isEmptySet a = (nrOfElts a) == 0 + +memberOfSet :: a Set -> Bool | Set a +memberOfSet _ (Set []) = False +memberOfSet x (Set [(y,_,_):ys]) = isEqual y x || memberOfSet x (Set ys) + +dynMemberOfSet :: Dynamic Set -> Bool +dynMemberOfSet _ (Set []) = False +dynMemberOfSet x (Set [(_,eq,_):ys]) = eq x || dynMemberOfSet x (Set ys) + +isSubset :: Set Set -> Bool +isSubset a b = (nrOfElts a) == (nrOfElts (intersection a b)) + +isStrictSubset :: Set Set -> Bool +isStrictSubset a b = isSubset a b && nrOfElts a < nrOfElts b + +union :: Set Set -> Set +union (Set a) (Set b) = Set (a ++ (fromSet (without (Set b) (Set a)))) +where  +	fromSet :: Set -> [(Dynamic, Dynamic -> Bool, String)] +	fromSet (Set x) = x + +intersection :: Set Set -> Set +intersection as (Set []) = as +intersection (Set as) (Set bs) = Set [(a,eq,ts) \\ (a,eq,ts) <- as | dynMemberOfSet a (Set bs)] + +without :: Set Set -> Set +without (Set as) (Set bs) = Set [(a,eq,ts) \\ (a,eq,ts) <- as | not (dynMemberOfSet a (Set bs))] + +Start = toString (union (toSet 1) (toSet 2)) diff --git a/1415/fp2/week3/camil/StdDynSet.prj b/1415/fp2/week3/camil/StdDynSet.prj new file mode 100644 index 0000000..4328042 --- /dev/null +++ b/1415/fp2/week3/camil/StdDynSet.prj @@ -0,0 +1,569 @@ +Version: 1.4
 +Global
 +	ProjectRoot:	.
 +	Built:	True
 +	Target:	Experimental
 +	Exec:	{Project}\StdDynSet.exe
 +	CodeGen
 +		CheckStacks:	False
 +		CheckIndexes:	True
 +	Application
 +		HeapSize:	2097152
 +		StackSize:	512000
 +		ExtraMemory:	81920
 +		IntialHeapSize:	204800
 +		HeapSizeMultiplier:	4096
 +		ShowExecutionTime:	False
 +		ShowGC:	False
 +		ShowStackSize:	False
 +		MarkingCollector:	False
 +		StandardRuntimeEnv:	True
 +		Profile
 +			Memory:	False
 +			MemoryMinimumHeapSize:	0
 +			Time:	False
 +			Stack:	False
 +		Output
 +			Output:	ShowConstructors
 +			Font:	Courier
 +			FontSize:	9
 +			WriteStdErr:	False
 +	Link
 +		LinkMethod:	Static
 +		GenerateRelocations:	False
 +		GenerateLinkMap:	False
 +		LinkResources:	False
 +		ResourceSource:	
 +		GenerateDLL:	False
 +		ExportedNames:	
 +	Paths
 +		Path:	{Project}
 +	Precompile:	
 +	Postlink:	
 +MainModule
 +	Name:	StdDynSet
 +	Dir:	{Project}
 +	Compiler
 +		NeverMemoryProfile:	False
 +		NeverTimeProfile:	False
 +		StrictnessAnalysis:	True
 +		ListTypes:	StrictExportTypes
 +		ListAttributes:	True
 +		Warnings:	True
 +		Verbose:	True
 +		ReadableABC:	False
 +		ReuseUniqueNodes:	True
 +		Fusion:	False
 +OtherModules
 +	Module
 +		Name:	StdCleanTypes
 +		Dir:	{Application}\Libraries\Dynamics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamic
 +		Dir:	{Application}\Libraries\Dynamics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	BitSet
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DefaultElem
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	EnDecode
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynIDMacros
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicUtilities
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicLowLevelInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicTypes
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicVersion
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemDynamic
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicGraphConversion
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicLinkerInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	read_function.obj
 +	Module
 +		Name:	memory
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	mem.obj
 +	Module
 +		Name:	memory_mapped_files
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	low.obj
 +		NeededLibraries
 +			Library:	StdDynamic_kernel32_library
 +	Module
 +		Name:	shared_buffer
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdBool
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdChar
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdCharList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdClass
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdEnv
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdFile
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdFunc
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdInt
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdMisc
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdOrdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdOverloaded
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdReal
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdString
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdTuple
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdMaybe
 +		Dir:	{Application}\Libraries\StdLib
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 diff --git a/1415/fp2/week3/camil/StdDynSet.prp b/1415/fp2/week3/camil/StdDynSet.prp new file mode 100644 index 0000000..87899a5 --- /dev/null +++ b/1415/fp2/week3/camil/StdDynSet.prp @@ -0,0 +1,217 @@ +Version: 1.4
 +MainModule
 +	Name:	StdDynSet
 +	Dir:	{Project}
 +	Dcl
 +		WindowPosition
 +			X:	65
 +			Y:	47
 +			SizeX:	800
 +			SizeY:	640
 +	DclOpen:	False
 +	Icl
 +		WindowPosition
 +			X:	10
 +			Y:	10
 +			SizeX:	800
 +			SizeY:	600
 +	IclOpen:	False
 +OtherModules
 +	Module
 +		Name:	StdCleanTypes
 +		Dir:	{Application}\Libraries\Dynamics
 +		Dcl
 +			WindowPosition
 +				X:	10
 +				Y:	10
 +				SizeX:	800
 +				SizeY:	600
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamic
 +		Dir:	{Application}\Libraries\Dynamics
 +		Dcl
 +			WindowPosition
 +				X:	276
 +				Y:	168
 +				SizeX:	800
 +				SizeY:	600
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	BitSet
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DefaultElem
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	EnDecode
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynIDMacros
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicUtilities
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicLowLevelInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicTypes
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicVersion
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemDynamic
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicGraphConversion
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicLinkerInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	memory
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	memory_mapped_files
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	shared_buffer
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdBool
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdChar
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdCharList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdClass
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdEnv
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdFile
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdFunc
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdInt
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdMisc
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdOrdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdOverloaded
 +		Dir:	{Application}\Libraries\StdEnv
 +		Dcl
 +			WindowPosition
 +				X:	10
 +				Y:	10
 +				SizeX:	800
 +				SizeY:	600
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdReal
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdString
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdTuple
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdMaybe
 +		Dir:	{Application}\Libraries\StdLib
 +		DclOpen:	False
 +		IclOpen:	False
 diff --git a/1415/fp2/week3/mart/GetallenRaden.icl b/1415/fp2/week3/mart/GetallenRaden.icl new file mode 100644 index 0000000..c1b2bb0 --- /dev/null +++ b/1415/fp2/week3/mart/GetallenRaden.icl @@ -0,0 +1,52 @@ +// Mart Lubbers s4109503, Camil Staps s4498062
 +
 +module GetallenRaden
 +
 +import StdEnv
 +import StdDynamic, StdDynamicFileIO
 +import StdFileSelect
 +
 +// Example generation program
 +//fib :: [Int]
 +//fib = [fib` i \\ i <- [0..]]
 +//	where 
 +//		fib` 0 = 0
 +//		fib` 1 = 1
 +//		fib` n = fib` (n-1) + fib` (n-2)
 +//
 +//Start :: *World -> (Bool, *World)
 +//Start world = writeDynamic "fib" (dynamic fib) world
 +
 +makeSeq :: Dynamic -> [Int]
 +makeSeq (x :: [Int]) = x
 +makeSeq _ = abort "You selected a file not containing a sequence"
 +
 +basename :: String Int -> String
 +basename s 0 = toString s.[0]
 +basename s n = let c = toString s.[n] in if (c == "\\") "" ((basename s (n-1)) +++ c)
 +
 +loadSeq :: String *World -> *([Int], String, *World)
 +loadSeq s world
 +# s = let l = size s in s % (0, l-5)
 +# (ok, dyn, world) = readDynamic s world
 +| not ok = abort "You didn't select a dynamic file"
 +| otherwise = (makeSeq dyn, basename s ((size s)-1), world)
 +
 +play :: *File String [Int] Int Int -> *File
 +play io _ _ _ 5 = io <<< "Congratulations, you had 5 correct answers\n"
 +play io seqname [nextnum:sequence] currentnum correct
 +# io = io <<< (seqname +++ "[" +++ toString currentnum +++ "] = " +++ toString nextnum +++ "\n")
 +# (ok, guessednumber, io) = freadi io
 +| not ok = play (snd (freadline io)) seqname sequence (currentnum + 1) correct
 +# (io, correct) = if (guessednumber == hd sequence) (io, correct+1) (io <<< "Incorrect...\n", correct) 
 += play (snd (freadline io)) seqname sequence (currentnum + 1) correct
 +
 +Start :: *World -> *World
 +Start world
 +# (inputfilepath, world) = selectInputFile world
 +| isNothing inputfilepath = abort "Please select a file"
 +# (sequence, sequencename, world) = loadSeq (fromJust inputfilepath) world
 +# (io, world) = stdio world
 +# io = (play io sequencename sequence 0 0) <<< "Press any key to close"
 +# (_, world) = fclose io world
 += world
 diff --git a/1415/fp2/week3/mart/GetallenRaden.prj b/1415/fp2/week3/mart/GetallenRaden.prj new file mode 100644 index 0000000..e857306 --- /dev/null +++ b/1415/fp2/week3/mart/GetallenRaden.prj @@ -0,0 +1,1594 @@ +Version: 1.4
 +Global
 +	ProjectRoot:	.
 +	Built:	True
 +	Target:	Object IO
 +	Exec:	{Project}\GetallenRaden.exe
 +	CodeGen
 +		CheckStacks:	False
 +		CheckIndexes:	True
 +	Application
 +		HeapSize:	2097152
 +		StackSize:	512000
 +		ExtraMemory:	81920
 +		IntialHeapSize:	204800
 +		HeapSizeMultiplier:	4096
 +		ShowExecutionTime:	False
 +		ShowGC:	False
 +		ShowStackSize:	False
 +		MarkingCollector:	False
 +		StandardRuntimeEnv:	True
 +		Profile
 +			Memory:	False
 +			MemoryMinimumHeapSize:	0
 +			Time:	False
 +			Stack:	False
 +		Output
 +			Output:	NoReturnType
 +			Font:	Courier
 +			FontSize:	9
 +			WriteStdErr:	False
 +	Link
 +		LinkMethod:	Dynamic
 +		GenerateRelocations:	False
 +		GenerateLinkMap:	False
 +		LinkResources:	False
 +		ResourceSource:	
 +		GenerateDLL:	False
 +		ExportedNames:	
 +	Paths
 +		Path:	{Project}
 +		Path:	{Application}\Libraries\Dynamics
 +		Path:	{Application}\Libraries\Dynamics\implementation
 +		Path:	{Application}\Libraries\Dynamics\implementation\windows
 +		Path:	{Application}\Libraries\Dynamics\general
 +		Path:	{Application}\Libraries\Directory
 +	Precompile:	
 +	Postlink:	
 +MainModule
 +	Name:	GetallenRaden
 +	Dir:	{Project}
 +	Compiler
 +		NeverMemoryProfile:	False
 +		NeverTimeProfile:	False
 +		StrictnessAnalysis:	True
 +		ListTypes:	StrictExportTypes
 +		ListAttributes:	True
 +		Warnings:	True
 +		Verbose:	True
 +		ReadableABC:	False
 +		ReuseUniqueNodes:	True
 +		Fusion:	False
 +OtherModules
 +	Module
 +		Name:	StdCleanTypes
 +		Dir:	{Application}\Libraries\Dynamics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamic
 +		Dir:	{Application}\Libraries\Dynamics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicFileIO
 +		Dir:	{Application}\Libraries\Dynamics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynID
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynIDMacros
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicUtilities
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicLowLevelInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicTypes
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicVersion
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemDynamic
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicGraphConversion
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicLinkerInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	read_function.obj
 +	Module
 +		Name:	memory
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	mem.obj
 +	Module
 +		Name:	memory_mapped_files
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	low.obj
 +		NeededLibraries
 +			Library:	StdDynamic_kernel32_library
 +	Module
 +		Name:	shared_buffer
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	BitSet
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DefaultElem
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	EnDecode
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	md5
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Directory
 +		Dir:	{Application}\Libraries\Directory
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	cDirectory.
 +	Module
 +		Name:	StdBitmap
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdControlDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdFileSelect
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdIOBasic
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdIOCommon
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdId
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdKey
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdMenuDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdPSt
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdPicture
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdPictureDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdProcessAttribute
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdProcessDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdTimerDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdWindowDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	cast
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	commondef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	device
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	deviceevents
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	devicefunctions
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	devicesystemstate
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	id
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iostate
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	keyfocus
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	menuhandle
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	processhandle
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	processstack
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	receiverhandle
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	receivermessage
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	receivertable
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	roundrobin
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	scheduler
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	semidynamic
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	systemid
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	timerhandle
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	timertable
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	windowhandle
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	world
 +		Dir:	{Application}\Libraries\ObjectIO
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	clCCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	util_121.
 +			ObjectFile:	cpicture_121.
 +			ObjectFile:	cdebug_121.
 +			ObjectFile:	cCrossCall_121.
 +			ObjectFile:	cCrossCallWindows_121.
 +			ObjectFile:	cCCallWindows_121.
 +			ObjectFile:	cCCallSystem_121.
 +	Module
 +		Name:	clCrossCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	cCrossCallWindows_121.
 +			ObjectFile:	cCrossCallProcedureTable_121.
 +			ObjectFile:	cCrossCallCursor_121.
 +			ObjectFile:	cCrossCall_121.
 +			ObjectFile:	cCCallSystem_121.
 +			ObjectFile:	cCCallWindows_121.
 +			ObjectFile:	cAcceleratorTable_121.
 +		NeededLibraries
 +			Library:	userExt_library
 +			Library:	gdiExt_library
 +			Library:	kernelExt_library
 +			Library:	winspool_library
 +			Library:	winmm_library
 +			Library:	shell32_library
 +			Library:	ole32_library
 +			Library:	kernel32_library
 +			Library:	comctl32_library
 +			Library:	advapi32_library
 +	Module
 +		Name:	menuCCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	cCrossCallMenus_121.
 +	Module
 +		Name:	menuCrossCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	osactivaterequests
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	osbeep
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	osbitmap
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	osdocumentinterface
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	cCrossCallxDI_121.
 +	Module
 +		Name:	osevent
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	osfileselect
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	cCrossCallFileSelectors_121.
 +	Module
 +		Name:	osfont
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	osguishare
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	oskey
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	osmenu
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	osmouse
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	ospicture
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	osrgn
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	ossystem
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	ostime
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	ostoolbar
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	ostoolbox
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	cCrossCallFont_121.
 +	Module
 +		Name:	ostypes
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	pictCCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	rgnCCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	windowCCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	cpicture_121.
 +			ObjectFile:	cCCallWindows_121.
 +	Module
 +		Name:	windowCrossCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdBool
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdChar
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdCharList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdClass
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdEnv
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdFile
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdFunc
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdInt
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdMisc
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdOrdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdOverloaded
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdReal
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdString
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdTuple
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdArrayExtensions
 +		Dir:	{Application}\Libraries\StdLib
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdLibMisc
 +		Dir:	{Application}\Libraries\StdLib
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdMaybe
 +		Dir:	{Application}\Libraries\StdLib
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 diff --git a/1415/fp2/week3/mart/GetallenRaden.prp b/1415/fp2/week3/mart/GetallenRaden.prp new file mode 100644 index 0000000..cc79889 --- /dev/null +++ b/1415/fp2/week3/mart/GetallenRaden.prp @@ -0,0 +1,543 @@ +Version: 1.4
 +MainModule
 +	Name:	GetallenRaden
 +	Dir:	{Project}
 +	DclOpen:	False
 +	Icl
 +		WindowPosition
 +			X:	10
 +			Y:	10
 +			SizeX:	800
 +			SizeY:	600
 +	IclOpen:	False
 +OtherModules
 +	Module
 +		Name:	StdCleanTypes
 +		Dir:	{Application}\Libraries\Dynamics
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamic
 +		Dir:	{Application}\Libraries\Dynamics
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicFileIO
 +		Dir:	{Application}\Libraries\Dynamics
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynID
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynIDMacros
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicUtilities
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicLowLevelInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicTypes
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicVersion
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemDynamic
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicGraphConversion
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicLinkerInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	memory
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	memory_mapped_files
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	shared_buffer
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	BitSet
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DefaultElem
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	EnDecode
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	md5
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Directory
 +		Dir:	{Application}\Libraries\Directory
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdBitmap
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdControlDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdFileSelect
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdIOBasic
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdIOCommon
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdId
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdKey
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdMenuDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdPSt
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdPicture
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdPictureDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdProcessAttribute
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdProcessDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdTimerDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdWindowDef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	cast
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	commondef
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	device
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	deviceevents
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	devicefunctions
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	devicesystemstate
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	id
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iostate
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	keyfocus
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	menuhandle
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	processhandle
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	processstack
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	receiverhandle
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	receivermessage
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	receivertable
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	roundrobin
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	scheduler
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	semidynamic
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	systemid
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	timerhandle
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	timertable
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	windowhandle
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	world
 +		Dir:	{Application}\Libraries\ObjectIO
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	clCCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	clCrossCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	menuCCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	menuCrossCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osactivaterequests
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osbeep
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osbitmap
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osdocumentinterface
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osevent
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osfileselect
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osfont
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osguishare
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	oskey
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osmenu
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osmouse
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	ospicture
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	osrgn
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	ossystem
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	ostime
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	ostoolbar
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	ostoolbox
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	ostypes
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	pictCCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	rgnCCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	windowCCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	windowCrossCall_12
 +		Dir:	{Application}\Libraries\ObjectIO\OS Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdBool
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdChar
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdCharList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdClass
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdEnv
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdFile
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdFunc
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdInt
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdMisc
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdOrdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdOverloaded
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdReal
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdString
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdTuple
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdArrayExtensions
 +		Dir:	{Application}\Libraries\StdLib
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdLibMisc
 +		Dir:	{Application}\Libraries\StdLib
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdMaybe
 +		Dir:	{Application}\Libraries\StdLib
 +		DclOpen:	False
 +		IclOpen:	False
 diff --git a/1415/fp2/week3/mart/NotatieDynamics.icl b/1415/fp2/week3/mart/NotatieDynamics.icl new file mode 100644 index 0000000..da90675 --- /dev/null +++ b/1415/fp2/week3/mart/NotatieDynamics.icl @@ -0,0 +1,25 @@ +module NotatieDynamics
 +
 +import StdEnv
 +import StdDynamic, StdDynamicFileIO
 +
 +Start = f4 f3
 +
 +f1 :: Int Int -> Int
 +f1 (x :: Int) y = x + y
 +
 +f2 :: Bool a a -> a
 +f2 (b :: Bool) (e1 :: a) (e2 :: a) = dynamic if b e1 e2 :: a
 +
 +f3 :: [Int]
 +f3 = dynamic map fib [1 ..]
 +
 +fib 0 = 1
 +fib 1 = 1
 +fib n = fib (n-1) + fib (n-2)
 +
 +f4 :: [Int] -> [Int]
 +f4 (xs :: [Int]) = take 10 xs
 +
 +f5 :: [Int] -> [Int]
 +f5 = f4 f3
 diff --git a/1415/fp2/week3/mart/StdDynSet.dcl b/1415/fp2/week3/mart/StdDynSet.dcl new file mode 100644 index 0000000..de9a9b7 --- /dev/null +++ b/1415/fp2/week3/mart/StdDynSet.dcl @@ -0,0 +1,24 @@ +definition module StdDynSet
 +
 +import StdOverloaded
 +
 +class Set a | TC, ==, toString a
 +
 +:: Set
 +
 +instance zero     Set
 +instance toString Set
 +instance ==       Set
 +
 +toSet			:: a       -> Set  | Set a
 +
 +nrOfElts		::     Set -> Int
 +isEmptySet		::     Set -> Bool
 +
 +memberOfSet		:: a   Set -> Bool | Set a
 +isSubset		:: Set Set -> Bool
 +isStrictSubset	:: Set Set -> Bool
 +
 +union			:: Set Set -> Set
 +intersection	:: Set Set -> Set
 +without			:: Set Set -> Set
 diff --git a/1415/fp2/week3/mart/StdDynSet.icl b/1415/fp2/week3/mart/StdDynSet.icl new file mode 100644 index 0000000..1202ce2 --- /dev/null +++ b/1415/fp2/week3/mart/StdDynSet.icl @@ -0,0 +1,54 @@ +implementation module StdDynSet
 +
 +import StdEnv
 +import StdDynamic
 +
 +class Set a | TC, ==, toString a
 +
 +:: Set = Set [Dynamic]
 +
 +instance zero     Set
 +where zero = Set []
 +
 +instance toString Set
 +where toString (Set a) = abort "toString not implemented"
 +	
 +instance == Set
 +where 
 +	(==) (Set []) (Set []) = True
 +	(==) (Set []) _ = False
 +	(==) _ (Set []) = False
 +
 +toSet :: a -> Set | Set a
 +toSet a = Set [dynamic a]
 +
 +nrOfElts :: Set -> Int
 +nrOfElts (Set a) = length a
 +
 +isEmptySet :: Set -> Bool
 +isEmptySet (Set []) = True
 +isEmptySet _ = False
 +
 +memberOfSet :: a Set -> Bool | Set a
 +memberOfSet _ (Set []) = False
 +memberOfSet x (Set [y:xs])
 +| isEqual x y = True
 +| otherwise = memberOfSet x xs
 +
 +isSubset :: Set Set -> Bool
 +isSubset a b = abort "isSubset nog niet geimplementeerd.\n"
 +
 +isStrictSubset :: Set Set -> Bool
 +isStrictSubset a b = abort "isStrictSubset nog niet geimplementeerd.\n"
 +
 +union :: Set Set -> Set
 +union a b = abort "union nog niet geimplementeerd.\n"
 +
 +intersection :: Set Set -> Set
 +intersection a b = abort "intersection nog niet geimplementeerd.\n"
 +
 +without :: Set Set -> Set
 +without a b = abort "without nog niet geimplementeerd.\n"
 +
 +Start :: Set
 +Start = toSet 1
 diff --git a/1415/fp2/week3/mart/StdDynSet.prj b/1415/fp2/week3/mart/StdDynSet.prj new file mode 100644 index 0000000..4328042 --- /dev/null +++ b/1415/fp2/week3/mart/StdDynSet.prj @@ -0,0 +1,569 @@ +Version: 1.4
 +Global
 +	ProjectRoot:	.
 +	Built:	True
 +	Target:	Experimental
 +	Exec:	{Project}\StdDynSet.exe
 +	CodeGen
 +		CheckStacks:	False
 +		CheckIndexes:	True
 +	Application
 +		HeapSize:	2097152
 +		StackSize:	512000
 +		ExtraMemory:	81920
 +		IntialHeapSize:	204800
 +		HeapSizeMultiplier:	4096
 +		ShowExecutionTime:	False
 +		ShowGC:	False
 +		ShowStackSize:	False
 +		MarkingCollector:	False
 +		StandardRuntimeEnv:	True
 +		Profile
 +			Memory:	False
 +			MemoryMinimumHeapSize:	0
 +			Time:	False
 +			Stack:	False
 +		Output
 +			Output:	ShowConstructors
 +			Font:	Courier
 +			FontSize:	9
 +			WriteStdErr:	False
 +	Link
 +		LinkMethod:	Static
 +		GenerateRelocations:	False
 +		GenerateLinkMap:	False
 +		LinkResources:	False
 +		ResourceSource:	
 +		GenerateDLL:	False
 +		ExportedNames:	
 +	Paths
 +		Path:	{Project}
 +	Precompile:	
 +	Postlink:	
 +MainModule
 +	Name:	StdDynSet
 +	Dir:	{Project}
 +	Compiler
 +		NeverMemoryProfile:	False
 +		NeverTimeProfile:	False
 +		StrictnessAnalysis:	True
 +		ListTypes:	StrictExportTypes
 +		ListAttributes:	True
 +		Warnings:	True
 +		Verbose:	True
 +		ReadableABC:	False
 +		ReuseUniqueNodes:	True
 +		Fusion:	False
 +OtherModules
 +	Module
 +		Name:	StdCleanTypes
 +		Dir:	{Application}\Libraries\Dynamics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamic
 +		Dir:	{Application}\Libraries\Dynamics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	BitSet
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DefaultElem
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	EnDecode
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynIDMacros
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicUtilities
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicLowLevelInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicTypes
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicVersion
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemDynamic
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicGraphConversion
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicLinkerInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	read_function.obj
 +	Module
 +		Name:	memory
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	mem.obj
 +	Module
 +		Name:	memory_mapped_files
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	low.obj
 +		NeededLibraries
 +			Library:	StdDynamic_kernel32_library
 +	Module
 +		Name:	shared_buffer
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdBool
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdChar
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdCharList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdClass
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdEnv
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdFile
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdFunc
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdInt
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdMisc
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdOrdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdOverloaded
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdReal
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdString
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdTuple
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdMaybe
 +		Dir:	{Application}\Libraries\StdLib
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 diff --git a/1415/fp2/week3/mart/StdDynSet.prp b/1415/fp2/week3/mart/StdDynSet.prp new file mode 100644 index 0000000..f2a25e4 --- /dev/null +++ b/1415/fp2/week3/mart/StdDynSet.prp @@ -0,0 +1,193 @@ +Version: 1.4
 +MainModule
 +	Name:	StdDynSet
 +	Dir:	{Project}
 +	DclOpen:	False
 +	Icl
 +		WindowPosition
 +			X:	10
 +			Y:	10
 +			SizeX:	800
 +			SizeY:	600
 +	IclOpen:	False
 +OtherModules
 +	Module
 +		Name:	StdCleanTypes
 +		Dir:	{Application}\Libraries\Dynamics
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamic
 +		Dir:	{Application}\Libraries\Dynamics
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	BitSet
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DefaultElem
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	EnDecode
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynIDMacros
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicUtilities
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicLowLevelInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicTypes
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicVersion
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemDynamic
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicGraphConversion
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicLinkerInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	memory
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	memory_mapped_files
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	shared_buffer
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdBool
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdChar
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdCharList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdClass
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdEnv
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdFile
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdFunc
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdInt
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdMisc
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdOrdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdOverloaded
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdReal
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdString
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdTuple
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdMaybe
 +		Dir:	{Application}\Libraries\StdLib
 +		DclOpen:	False
 +		IclOpen:	False
 diff --git a/1415/fp2/week3/mart/fib.dyn b/1415/fp2/week3/mart/fib.dyn new file mode 100644 index 0000000..8b8335a --- /dev/null +++ b/1415/fp2/week3/mart/fib.dyn @@ -0,0 +1 @@ +0a49c9db651c81d64bfc61520d7cfd6b diff --git a/1415/fp2/week3/week3.tar.gz b/1415/fp2/week3/week3.tar.gzBinary files differ new file mode 100644 index 0000000..84c7697 --- /dev/null +++ b/1415/fp2/week3/week3.tar.gz diff --git a/1415/fp2/week45/camil/RefactorX.dcl b/1415/fp2/week45/camil/RefactorX.dcl new file mode 100644 index 0000000..3ddc8a4 --- /dev/null +++ b/1415/fp2/week45/camil/RefactorX.dcl @@ -0,0 +1,18 @@ +definition module RefactorX
 +
 +import StdEnv
 +
 +::	Expr			= NR   Int
 +					| VAR  Name
 +					| OP   Expr Operator Expr
 +					| LET  Name     Expr Expr
 +::	Name		  :== String
 +::	Operator		= PLUS | MIN | MUL | DIV
 +::	Val				= Result Int | Undef
 +
 +from StdClass import class toString
 +
 +instance toString Expr
 +free				:: Expr -> [Name]
 +remove_unused_lets	:: Expr -> Expr
 +eval				:: Expr -> Val
 diff --git a/1415/fp2/week45/camil/RefactorX.icl b/1415/fp2/week45/camil/RefactorX.icl new file mode 100644 index 0000000..a7bf909 --- /dev/null +++ b/1415/fp2/week45/camil/RefactorX.icl @@ -0,0 +1,82 @@ +implementation module RefactorX
 +
 +import StdEnv
 +
 +Start = map eval [E1,E2,E3,E4,E5]
 +
 +E1 = OP (LET "x" (OP (NR 42) MIN (NR 3)) (OP (VAR "x") DIV (NR 0)))
 +	PLUS
 +	(LET "y" (NR 6) (OP (VAR "y") MUL (VAR "y")))
 +E2 = LET "x" (NR 42) (OP (VAR "x") PLUS (LET "x" (NR 58) (VAR "x")))
 +E3 = LET "x" (NR 1) (LET "y" (NR 2) (LET "x" (NR 3) (NR 4)))
 +E4 = LET "x" (NR 1) (OP (VAR "x") PLUS (VAR "y"))
 +E5 = OP (LET "x" (NR 1) (VAR "x")) MUL (VAR "x")
 +
 +::	Expr							= NR   Int
 +									| VAR  Name
 +									| OP   Expr Operator Expr
 +									| LET  Name     Expr Expr
 +::	Name							:== String
 +::	Operator						= PLUS | MIN | MUL | DIV
 +::	Val								= Result Int | Undef
 +
 +(<+) infixl 9 :: String a -> String | toString a
 +(<+) str a = str +++ toString a
 +
 +instance toString Operator where
 +	toString PLUS = "+"
 +	toString MIN = "-"
 +	toString MUL = "*"
 +	toString DIV = "/"
 +
 +//  expressies afdrukken:
 +instance toString Expr where
 +	toString (NR n) = toString n
 +	toString (VAR s) = s
 +	toString (LET s e1 e2) = "let " <+ s <+ " = " <+ e1 <+ " in " <+ e2
 +	toString (OP e1 o e2) = bracket e1 <+ o <+ bracket e2
 +	where
 +		bracket :: Expr -> String
 +		bracket (OP e1 o e2) = "(" <+ e1 <+ o <+ e2 <+ ")"
 +		bracket (LET s e1 e2) = "(" <+ (LET s e1 e2) <+ ")"
 +		bracket x = toString x
 +
 +//	vrije variabelen:
 +free								:: Expr -> [Name]
 +free (NR _) = []
 +free (VAR s) = [s]
 +free (LET s _ e2) = [n \\ n <- free e2 | n <> s]
 +free (OP e1 _ e2) = removeDup ((free e1) ++ (free e2))
 +
 +//	verwijder deelexpressies met ongebruikte let-variabelen:
 +remove_unused_lets					:: Expr -> Expr
 +remove_unused_lets (LET s e1 e2)
 +| isMember s (free e2) = (LET s (remove_unused_lets e1) (remove_unused_lets e2))
 +| otherwise = remove_unused_lets e2
 +remove_unused_lets (OP e1 o e2) = OP (remove_unused_lets e1) o (remove_unused_lets e2)
 +remove_unused_lets x = x
 +
 +//	evaluator met tabel van naam-waarde paren:
 +eval								:: Expr -> Val
 +eval e = eval` e []
 +where
 +	eval` :: Expr [(Name, Val)] -> Val
 +	eval` (NR n) vs = Result n
 +	eval` (VAR s) vs = find s vs
 +	where
 +		find :: Name [(Name, Val)] -> Val
 +		find _ [] = Undef
 +		find s [(t,v):vs]
 +		| s == t = v
 +		| otherwise = find s vs
 +	eval` (LET s e1 e2) vs = eval` e2 [(s,eval` e1 vs):vs]
 +	eval` (OP e1 o e2) vs = op o (eval` e1 vs) (eval` e2 vs)
 +	where
 +		op :: Operator Val Val -> Val
 +		op _ Undef _ = Undef
 +		op _ _ Undef = Undef
 +		op PLUS (Result x) (Result y) = Result (x + y)
 +		op MIN (Result x) (Result y) = Result (x - y)
 +		op MUL (Result x) (Result y) = Result (x * y)
 +		op DIV _ (Result 0) = Undef
 +		op DIV (Result x) (Result y) = Result (x / y)
 diff --git a/1415/fp2/week45/mart/RefactorX.dcl b/1415/fp2/week45/mart/RefactorX.dcl new file mode 100644 index 0000000..393c097 --- /dev/null +++ b/1415/fp2/week45/mart/RefactorX.dcl @@ -0,0 +1,17 @@ +// Mart Lubbers s4109503, Camil Staps s4498062
 +
 +definition module RefactorX
 +
 +from StdClass import class toString
 +import StdEnv
 +
 +:: Expr = NR Int | VAR Name | OP Expr Operator Expr | LET Name Expr Expr
 +:: Name :== String
 +:: Operator = PLUS | MIN | MUL | DIV
 +:: Val = Result Int | Undef
 +
 +
 +instance toString Expr
 +free :: Expr -> [Name]
 +remove_unused_lets :: Expr -> Expr
 +eval :: Expr -> Val
 diff --git a/1415/fp2/week45/mart/RefactorX.icl b/1415/fp2/week45/mart/RefactorX.icl new file mode 100644 index 0000000..c74df08 --- /dev/null +++ b/1415/fp2/week45/mart/RefactorX.icl @@ -0,0 +1,72 @@ +// Mart Lubbers s4109503, Camil Staps s4498062
 +
 +implementation module RefactorX
 +
 +import StdEnv
 +
 +//Start = map toString [E1,E2,E3,E4,E5]
 +//Start = map free [E1,E2,E3,E4,E5]
 +//Start = map toString (map remove_unused_lets [E1,E2,E3,E4,E5])
 +Start = map eval [E1,E2,E3,E4,E5]
 +	where
 +		E1 = OP (LET "x" (OP (NR 42) MIN (NR 3)) (OP (VAR "x") DIV (NR 0))) PLUS (LET "y" (NR 6) (OP (VAR "y") MUL (VAR "y")))
 +		E2 = LET "x" (NR 42) (OP (VAR "x") PLUS (LET "x" (NR 58) (VAR "x")))
 +		E3 = LET "x" (NR 1) (LET "y" (NR 2) (LET "x" (NR 3) (NR 4)))
 +		E4 = LET "x" (NR 1) (OP (VAR "x") PLUS (VAR "y"))
 +		E5 = OP (LET "x" (NR 1) (VAR "x")) MUL (VAR "x")
 +
 +(<+) infixl 9 :: String a -> String | toString a
 +(<+) str a = str +++ toString a
 +
 +instance toString Operator where
 +	toString PLUS = "+"
 +	toString MIN = "-"
 +	toString MUL = "*"
 +	toString DIV = "/"
 + 
 +instance toString Expr where
 +	toString (NR n) = toString n
 +	toString (VAR v) = v
 +	toString (LET n e1 e2) = "(let " <+ n <+ "=" <+ e1 <+ " in " <+ e2 <+ ")"
 +	toString (OP e1 o e2) = bracket e1 <+ o <+ bracket e2
 +		where
 +			bracket :: Expr -> String
 +			bracket (OP e1 o e2) = "(" <+ (OP e1 o e2) <+ ")"
 +			bracket e = toString e
 +
 +free:: Expr -> [Name]
 +free (NR n) = [] 
 +free (VAR v) = [v]
 +free (OP e1 o e2) = removeDup (free e1 ++ free e2)
 +free (LET n e1 e2) = removeMember n (free e2)
 +
 +remove_unused_lets:: Expr -> Expr
 +remove_unused_lets (LET n e1 e2)
 +| isMember n (free e2) = (LET n (remove_unused_lets e1) (remove_unused_lets e2))
 +| otherwise = remove_unused_lets e2
 +remove_unused_lets (OP e1 o e2) = (OP (remove_unused_lets e1) o (remove_unused_lets e2))
 +remove_unused_lets e = e
 +
 +apply:: Operator Val Val -> Val
 +apply _ Undef _ = Undef
 +apply _ _ Undef = Undef
 +apply DIV _ (Result 0) = Undef
 +apply o (Result e1) (Result e2) = Result (apply` o e1 e2)
 +	where 
 +		apply`:: Operator -> Int Int -> Int
 +		apply` PLUS = +
 +		apply` MIN = -
 +		apply` MUL = *
 +		apply` DIV = /
 +
 +eval:: Expr -> Val
 +eval e = eval` e []
 +	where
 +		eval`:: Expr [(Name, Val)] -> Val
 +		eval` (NR n) _ = Result n
 +		eval` (VAR v) [] = Undef
 +		eval` (VAR v) [(n, e):xs]
 +		| v == n = e
 +		| otherwise = eval` (VAR v) xs
 +		eval` (OP e1 o e2) xs = apply o (eval` e1 xs) (eval` e2 xs)
 +		eval` (LET n e1 e2) xs = eval` e2 [(n, eval` e1 xs):xs]
 diff --git a/1415/fp2/week45/week45.tar.gz b/1415/fp2/week45/week45.tar.gzBinary files differ new file mode 100644 index 0000000..690e838 --- /dev/null +++ b/1415/fp2/week45/week45.tar.gz diff --git a/1415/fp2/week6/camil/BinSearchTree.dcl b/1415/fp2/week6/camil/BinSearchTree.dcl new file mode 100644 index 0000000..8b2ab3a --- /dev/null +++ b/1415/fp2/week6/camil/BinSearchTree.dcl @@ -0,0 +1,8 @@ +definition module BinSearchTree + +import StdClass +import BinTree + +is_geordend     :: (BTree a) -> Bool | Ord a // meest algemene type +is_gebalanceerd :: (BTree a) -> Bool | Ord a // meest algemene type +insertTree :: a (BTree a) -> BTree a | Ord a
\ No newline at end of file diff --git a/1415/fp2/week6/camil/BinSearchTree.icl b/1415/fp2/week6/camil/BinSearchTree.icl new file mode 100644 index 0000000..83ca73b --- /dev/null +++ b/1415/fp2/week6/camil/BinSearchTree.icl @@ -0,0 +1,49 @@ +// Mart Lubbers, s4109503 +// Camil Staps, s4498062 + +implementation module BinSearchTree + +import StdEnv +import BinTree + +insertTree :: a (BTree a) -> BTree a | Ord a +insertTree e BLeaf = BNode e BLeaf BLeaf +insertTree e (BNode x le ri) +| e <= x = BNode x (insertTree e le) ri +| e >  x = BNode x le (insertTree e ri) + +deleteTree :: a (BTree a) -> (BTree a) | Eq, Ord a +deleteTree e BLeaf = BLeaf +deleteTree e (BNode x le ri) +| e <  x = BNode x (deleteTree e le) ri +| e == x = join le ri +| e >  x = BNode x le (deleteTree e ri) +where +    join :: (BTree a) (BTree a) -> (BTree a) +    join BLeaf b2 = b2 +    join b1 b2 = BNode x b1` b2 +    where +        (x,b1`) = largest b1 +         +        largest :: (BTree a) -> (a,(BTree a)) +        largest (BNode x b1 BLeaf) = (x,b1) +        largest (BNode x b1 b2)   = (y,BNode x b1 b2`) +        where +            (y,b2`) = largest b2 + + +is_geordend :: (BTree a) -> Bool | Ord a // meest algemene type +is_geordend BLeaf = True +is_geordend (BNode x le ri) = (foldr (&&) True (map ((>) x) (members le))) && (foldr (&&) True (map ((<=) x) (members ri))) && is_geordend le && is_geordend ri +where +    members :: (BTree a) -> [a] +    members BLeaf = [] +    members (BNode x le ri) = [x:(members le) ++ (members ri)] + +is_gebalanceerd :: (BTree a) -> Bool | Ord a // meest algemene type +is_gebalanceerd BLeaf = True +is_gebalanceerd (BNode x le ri) = abs ((depth le) - (depth ri)) <= 1 && is_gebalanceerd le && is_gebalanceerd ri +where +    depth :: (BTree a) -> Int +    depth BLeaf = 0 +    depth (BNode x le ri) = max (depth le) (depth ri) + 1
\ No newline at end of file diff --git a/1415/fp2/week6/camil/BinSearchTreeImage.icl b/1415/fp2/week6/camil/BinSearchTreeImage.icl new file mode 100644 index 0000000..00ae8b1 --- /dev/null +++ b/1415/fp2/week6/camil/BinSearchTreeImage.icl @@ -0,0 +1,75 @@ +module BinSearchTreeImage + +/* Instructions: + +(1) copy BinTree.(i/d)cl and BinSearchTree.(i/d)cl from Practicum to +    {iTasks-SDK}\Experiments\SVG_tests\ +     +(2) in these modules change the type + +    :: Tree a = Node a (Tree a) (Tree a) | Leaf +     +    to +     +    :: BTree a = BLeaf | BNode a (BTree a) (BTree a)	// ORDER OF DATACONSTRUCTORS IS ESSENTIAL!! +     +    and adapt the corresponding function definitions. +     +(3) this main file (BinSearchTreeImage.icl) must be in the same folder: +    {iTasks-SDK}\Experiments\SVG_tests\ +     +(4) create a new project and set de environment to 'iTasks' + +(5) Bring-Up-To-Date and start generated application + +(6) Open a browser and navigate to localhost. +    The application creates two tasks: +    (a) The task on the left allows you to enter subsequent elements that are inserted in the tree, one after another. +    (b) The task on the right must be finished by you by writing the function treeImage. This function must render the tree structure in such a way +        that Nodes of the same depth have the same y-coordinate, and the root having the smallest y-coordinate. +*/ + +import iTasks								// de algemene iTask API +import iTasks.API.Extensions.SVG.SVGlet		// specialiseer task editors +from   StdFunc import flip + +import BinSearchTree						// type definition of Tree and sample trees z0 .. z8 +derive class iTask BTree + +Start				:: *World -> *World +Start world			= startEngine [publish "/" (WebApp []) (\_ -> task)] world + +task				:: Task [Int] +task				= withShared [] (\sharedList -> +						(  (updateSharedInformation (Title "Edit list") [] sharedList <<@ ArrangeHorizontal) +						   -||- +						   (viewSharedInformation (Title "Tree view") [imageView treeImage` (\_ _ -> Nothing)] sharedList <<@ ArrangeHorizontal) +						) <<@ ArrangeHorizontal +					  ) <<@ FullScreen + +font				= normalFontDef "Courier New" fonthoogte +fonthoogte			= 14.0 + +treeImage`			:: [Int] *TagSource -> Image m +treeImage` nrs tags	= fst(treeImage (foldl (flip insertTree) BLeaf nrs) tags) + +TMargin = 10.0 + +treeImage			:: (BTree Int) *TagSource -> (Image m, *TagSource) +treeImage BLeaf ts = (margin (px zero, px TMargin) (circle (px fonthoogte)), ts) +treeImage (BNode x t1 t2) [(tg1, utg1),(tg2, utg2):ts] += (above (repeat AtMiddleX) [] [textbox, lines, subtrees] Nothing, ts2) +	where +		(i1, ts1) = treeImage t1 ts +		(i2, ts2) = treeImage t2 ts1 +		subtrees = beside (repeat AtTop) [] [tag utg1 i1, tag utg2 i2] Nothing +		box = rect (textxspan font (toString x)) (px fonthoogte) <@< {fill=toSVGColor "none"} +		lines_with_subtrees = above (repeat AtMiddleX) [] [lines, subtrees] Nothing +		textbox = overlay (repeat (AtMiddleX, AtMiddleY)) [] [box, text font (toString x)] Nothing +		lines = beside (repeat AtBottom) [] [ +			empty (((imagexspan tg1) /. 2) - ((imagexspan tg2) /. 2)) (px TMargin), // ignored if negative +			line Nothing Slash ((imagexspan tg2) /. 2) (px TMargin), +			line Nothing Backslash ((imagexspan tg1) /. 2) (px TMargin), +			empty (((imagexspan tg2) /. 2) - ((imagexspan tg1) /. 2)) (px TMargin)] // ignored if negative +			Nothing + diff --git a/1415/fp2/week6/camil/BinSearchTreeImage.prj b/1415/fp2/week6/camil/BinSearchTreeImage.prj new file mode 100644 index 0000000..092183a --- /dev/null +++ b/1415/fp2/week6/camil/BinSearchTreeImage.prj @@ -0,0 +1,2645 @@ +Version: 1.4
 +Global
 +	ProjectRoot:	.
 +	Target:	iTasks
 +	Exec:	{Project}\BinSearchTreeImage.exe
 +	CodeGen
 +		CheckStacks:	False
 +		CheckIndexes:	True
 +	Application
 +		HeapSize:	134217728
 +		StackSize:	4194304
 +		ExtraMemory:	81920
 +		IntialHeapSize:	204800
 +		HeapSizeMultiplier:	4096
 +		ShowExecutionTime:	False
 +		ShowGC:	False
 +		ShowStackSize:	False
 +		MarkingCollector:	False
 +		StandardRuntimeEnv:	True
 +		Profile
 +			Memory:	False
 +			MemoryMinimumHeapSize:	0
 +			Time:	False
 +			Stack:	False
 +		Output
 +			Output:	ShowConstructors
 +			Font:	Courier
 +			FontSize:	9
 +			WriteStdErr:	False
 +	Link
 +		LinkMethod:	Static
 +		GenerateRelocations:	False
 +		GenerateLinkMap:	False
 +		LinkResources:	False
 +		ResourceSource:	
 +		GenerateDLL:	False
 +		ExportedNames:	
 +	Paths
 +		Path:	{Project}
 +	Precompile:	
 +	Postlink:	
 +MainModule
 +	Name:	BinSearchTreeImage
 +	Dir:	{Project}
 +	Compiler
 +		NeverMemoryProfile:	False
 +		NeverTimeProfile:	False
 +		StrictnessAnalysis:	True
 +		ListTypes:	StrictExportTypes
 +		ListAttributes:	True
 +		Warnings:	True
 +		Verbose:	True
 +		ReadableABC:	False
 +		ReuseUniqueNodes:	True
 +		Fusion:	False
 +OtherModules
 +	Module
 +		Name:	BinSearchTree
 +		Dir:	{Project}
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	BinTree
 +		Dir:	{Project}
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamic
 +		Dir:	{Application}\Libraries\Dynamics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	BitSet
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DefaultElem
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	EnDecode
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynIDMacros
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicUtilities
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicLowLevelInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicTypes
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDynamicVersion
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicGraphConversion
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	DynamicLinkerInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	read_function.obj
 +	Module
 +		Name:	memory
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	mem.obj
 +	Module
 +		Name:	memory_mapped_files
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	low.obj
 +		NeededLibraries
 +			Library:	StdDynamic_kernel32_library
 +	Module
 +		Name:	shared_buffer
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdBool
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdChar
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdCharList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdClass
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdDebug
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdEnv
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdFile
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdFunc
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdInt
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdMisc
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdOrdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdOverloaded
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdOverloadedList
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdReal
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdStrictLists
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdString
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdTuple
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemEnumStrict
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemStrictLists
 +		Dir:	{Application}\Libraries\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	TCPChannelClass
 +		Dir:	{Application}\Libraries\TCPIP
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	TCPDef
 +		Dir:	{Application}\Libraries\TCPIP
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	TCPEvent
 +		Dir:	{Application}\Libraries\TCPIP
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	TCPIP
 +		Dir:	{Application}\Libraries\TCPIP
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	TCPStringChannels
 +		Dir:	{Application}\Libraries\TCPIP
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	TCPStringChannelsInternal
 +		Dir:	{Application}\Libraries\TCPIP
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	ostcp
 +		Dir:	{Application}\Libraries\TCPIP
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	cTCP_121.
 +		NeededLibraries
 +			Library:	wsock_library
 +	Module
 +		Name:	tcp
 +		Dir:	{Application}\Libraries\TCPIP
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	tcp_bytestreams
 +		Dir:	{Application}\Libraries\TCPIP
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Control.Applicative
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Control.Monad
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Crypto.Hash.SHA1
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Either
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Error
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Foldable
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Func
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Functor
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Generic
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Graph
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.IntMap.Base
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.IntMap.Strict
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.List
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Map
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Maybe
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Monoid
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Set
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Traversable
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Tuple
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Data.Void
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Graphics.Scalable
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Graphics.Scalable.Internal
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Internet.HTTP
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Math.Random
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System.CommandLine
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System.FilePath
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System.IO
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System._Pointer
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.CSV
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Encodings.Base64
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Encodings.MIME
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Encodings.UrlEncoding
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.HTML
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.JSON
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.PPrint
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Parsers.ParserLanguage
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Parsers.Parsers
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Parsers.ParsersAccessories
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Parsers.ParsersDerived
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Parsers.ParsersKernel
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.StringAppender
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.URI
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Unicode
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Unicode.Encodings.JS
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Text.Unicode.UChar
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	WCsubst.
 +			ObjectFile:	bsearch.
 +	Module
 +		Name:	System.Directory
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System.Environment
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System.File
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System.OSError
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System.Process
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System.Time
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededLibraries
 +			Library:	msvcrt.txt
 +	Module
 +		Name:	System._WinBase
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededLibraries
 +			Library:	_WinBase_library
 +	Module
 +		Name:	System._WinDef
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System._Windows
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	System.OS
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows-32
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.FastString
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.Linker.LazyLinker
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.Linker.SaplLinkerShared
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.Optimization.StrictnessPropagation
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.SaplParser
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.SaplStruct
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.SaplTokenizer
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.Target.Flavour
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.Target.JS.CodeGeneratorJS
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.Transform.AddSelectors
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	Sapl.Transform.Let
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	dynamic_string
 +		Dir:	{Application}\iTasks-SDK\Dependencies\graph_copy
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	copy_string_to_graph.
 +			ObjectFile:	copy_string_to_graph_interface.
 +			ObjectFile:	copy_graph_to_string.
 +			ObjectFile:	copy_graph_to_string_interface.
 +	Module
 +		Name:	graph_to_sapl_string
 +		Dir:	{Application}\iTasks-SDK\Dependencies\graph_copy
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	graph_to_string_with_descriptors
 +		Dir:	{Application}\iTasks-SDK\Dependencies\graph_copy
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +		NeededObjFiles
 +			ObjectFile:	copy_graph_to_string.
 +			ObjectFile:	copy_graph_to_string_interface.
 +	Module
 +		Name:	sapldebug
 +		Dir:	{Application}\iTasks-SDK\Dependencies\graph_copy
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	_SystemDynamic
 +		Dir:	{Application}\iTasks-SDK\Patches\Dynamics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	GenEq
 +		Dir:	{Application}\iTasks-SDK\Patches\Generics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	GenLexOrd
 +		Dir:	{Application}\iTasks-SDK\Patches\Generics
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdGeneric
 +		Dir:	{Application}\iTasks-SDK\Patches\StdEnv
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	TCPChannels
 +		Dir:	{Application}\iTasks-SDK\Patches\TCPIP
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Common.DBTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Common.ExportTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Common.ImportTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Common.InteractionTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Common.SDSCombinators
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Common.TaskCombinators
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.Client.Component
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.Client.Editlet
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.Client.Interface
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.Client.Tasklet
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.IntegrationTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.LayoutCombinators
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.OptimizedCoreTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.SDSCombinators
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.SDSs
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.TaskCombinators
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.Tasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Core.Types
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Extensions.Admin.UserAdmin
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Extensions.Admin.WorkflowAdmin
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Extensions.SVG.SVGlet
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks.API.Extensions.User
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Client.JSStore
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Client.LinkerSupport
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Client.Override
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Client.RunOnClient
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Client.Tasklet
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.DynamicUtil
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Engine
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Generic
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Generic.Defaults
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Generic.Interaction
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Generic.Visualization
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.HtmlUtil
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.HttpUtil
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.IWorld
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.RemoteAccess
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.SDS
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.SDSService
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Serialization
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Store
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Task
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.TaskEval
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.TaskServer
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.TaskState
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.TaskStore
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Tonic
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Tonic.AbsSyn
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Tonic.Images
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Tonic.Pretty
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Tonic.Types
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.UIDefinition
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.UIDiff
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.Util
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	iTasks._Framework.WebService
 +		Dir:	{Application}\iTasks-SDK\Server
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 +	Module
 +		Name:	StdMaybe
 +		Dir:	{Application}\iTasks-SDK\Server\lib
 +		Compiler
 +			NeverMemoryProfile:	False
 +			NeverTimeProfile:	False
 +			StrictnessAnalysis:	True
 +			ListTypes:	StrictExportTypes
 +			ListAttributes:	True
 +			Warnings:	True
 +			Verbose:	True
 +			ReadableABC:	False
 +			ReuseUniqueNodes:	True
 +			Fusion:	False
 diff --git a/1415/fp2/week6/camil/BinSearchTreeImage.prp b/1415/fp2/week6/camil/BinSearchTreeImage.prp new file mode 100644 index 0000000..da58fb3 --- /dev/null +++ b/1415/fp2/week6/camil/BinSearchTreeImage.prp @@ -0,0 +1,922 @@ +Version: 1.4
 +MainModule
 +	Name:	BinSearchTreeImage
 +	Dir:	{Project}
 +	DclOpen:	False
 +	IclOpen:	True
 +OtherModules
 +	Module
 +		Name:	BinSearchTree
 +		Dir:	{Project}
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	BinTree
 +		Dir:	{Project}
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamic
 +		Dir:	{Application}\Libraries\Dynamics
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	BitSet
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DefaultElem
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	EnDecode
 +		Dir:	{Application}\Libraries\Dynamics\general
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynIDMacros
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicUtilities
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicLowLevelInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicTypes
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDynamicVersion
 +		Dir:	{Application}\Libraries\Dynamics\implementation
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicGraphConversion
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	DynamicLinkerInterface
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	memory
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	memory_mapped_files
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	shared_buffer
 +		Dir:	{Application}\Libraries\Dynamics\implementation\windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdBool
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdChar
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdCharList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdClass
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdDebug
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdEnv
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdFile
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdFunc
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdInt
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdMisc
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdOrdList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdOverloaded
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdOverloadedList
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdReal
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdStrictLists
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdString
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdTuple
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemArray
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemEnum
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemEnumStrict
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemStrictLists
 +		Dir:	{Application}\Libraries\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	TCPChannelClass
 +		Dir:	{Application}\Libraries\TCPIP
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	TCPDef
 +		Dir:	{Application}\Libraries\TCPIP
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	TCPEvent
 +		Dir:	{Application}\Libraries\TCPIP
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	TCPIP
 +		Dir:	{Application}\Libraries\TCPIP
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	TCPStringChannels
 +		Dir:	{Application}\Libraries\TCPIP
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	TCPStringChannelsInternal
 +		Dir:	{Application}\Libraries\TCPIP
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	ostcp
 +		Dir:	{Application}\Libraries\TCPIP
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	tcp
 +		Dir:	{Application}\Libraries\TCPIP
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	tcp_bytestreams
 +		Dir:	{Application}\Libraries\TCPIP
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Control.Applicative
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Control.Monad
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Crypto.Hash.SHA1
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Either
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Error
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Foldable
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Func
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Functor
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Generic
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Graph
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.IntMap.Base
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.IntMap.Strict
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.List
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Map
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Maybe
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Monoid
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Set
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Traversable
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Tuple
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Data.Void
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Graphics.Scalable
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Graphics.Scalable.Internal
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Internet.HTTP
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Math.Random
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System.CommandLine
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System.FilePath
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System.IO
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System._Pointer
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.CSV
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Encodings.Base64
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Encodings.MIME
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Encodings.UrlEncoding
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.HTML
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.JSON
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.PPrint
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Parsers.ParserLanguage
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Parsers.Parsers
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Parsers.ParsersAccessories
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Parsers.ParsersDerived
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Parsers.ParsersKernel
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.StringAppender
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.URI
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Unicode
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Unicode.Encodings.JS
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Text.Unicode.UChar
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Independent
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System.Directory
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System.Environment
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System.File
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System.OSError
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System.Process
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System.Time
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System._WinBase
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System._WinDef
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System._Windows
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	System.OS
 +		Dir:	{Application}\iTasks-SDK\Dependencies\Platform\OS-Windows-32
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.FastString
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.Linker.LazyLinker
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.Linker.SaplLinkerShared
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.Optimization.StrictnessPropagation
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.SaplParser
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.SaplStruct
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.SaplTokenizer
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.Target.Flavour
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.Target.JS.CodeGeneratorJS
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.Transform.AddSelectors
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	Sapl.Transform.Let
 +		Dir:	{Application}\iTasks-SDK\Dependencies\SAPL
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	dynamic_string
 +		Dir:	{Application}\iTasks-SDK\Dependencies\graph_copy
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	graph_to_sapl_string
 +		Dir:	{Application}\iTasks-SDK\Dependencies\graph_copy
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	graph_to_string_with_descriptors
 +		Dir:	{Application}\iTasks-SDK\Dependencies\graph_copy
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	sapldebug
 +		Dir:	{Application}\iTasks-SDK\Dependencies\graph_copy
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	_SystemDynamic
 +		Dir:	{Application}\iTasks-SDK\Patches\Dynamics
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	GenEq
 +		Dir:	{Application}\iTasks-SDK\Patches\Generics
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	GenLexOrd
 +		Dir:	{Application}\iTasks-SDK\Patches\Generics
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdGeneric
 +		Dir:	{Application}\iTasks-SDK\Patches\StdEnv
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	TCPChannels
 +		Dir:	{Application}\iTasks-SDK\Patches\TCPIP
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Common.DBTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Common.ExportTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Common.ImportTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Common.InteractionTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Common.SDSCombinators
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Common.TaskCombinators
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.Client.Component
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.Client.Editlet
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.Client.Interface
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.Client.Tasklet
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.IntegrationTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.LayoutCombinators
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.OptimizedCoreTasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.SDSCombinators
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.SDSs
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.TaskCombinators
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.Tasks
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Core.Types
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Extensions.Admin.UserAdmin
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Extensions.Admin.WorkflowAdmin
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Extensions.SVG.SVGlet
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks.API.Extensions.User
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Client.JSStore
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Client.LinkerSupport
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Client.Override
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Client.RunOnClient
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Client.Tasklet
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.DynamicUtil
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Engine
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Generic
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Generic.Defaults
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Generic.Interaction
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Generic.Visualization
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.HtmlUtil
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.HttpUtil
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.IWorld
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.RemoteAccess
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.SDS
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.SDSService
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Serialization
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Store
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Task
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.TaskEval
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.TaskServer
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.TaskState
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.TaskStore
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Tonic
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Tonic.AbsSyn
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Tonic.Images
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Tonic.Pretty
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Tonic.Types
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.UIDefinition
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.UIDiff
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.Util
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	iTasks._Framework.WebService
 +		Dir:	{Application}\iTasks-SDK\Server
 +		DclOpen:	False
 +		IclOpen:	False
 +	Module
 +		Name:	StdMaybe
 +		Dir:	{Application}\iTasks-SDK\Server\lib
 +		DclOpen:	False
 +		IclOpen:	False
 diff --git a/1415/fp2/week6/camil/BinTree.dcl b/1415/fp2/week6/camil/BinTree.dcl new file mode 100644 index 0000000..e8b1700 --- /dev/null +++ b/1415/fp2/week6/camil/BinTree.dcl @@ -0,0 +1,16 @@ +definition module BinTree + +::  BTree a = BNode a (BTree a) (BTree a) | BLeaf + +t0 :: BTree Int +t1 :: BTree Int +t2 :: BTree Int +t3 :: BTree Int +t4 :: BTree Int +t5 :: BTree Int +t6 :: BTree Int +t7 :: BTree Int + +//nodes  :: // meest algemene type +//leaves :: // meest algemene type +//diepte :: // meest algemene type diff --git a/1415/fp2/week6/camil/BinTree.icl b/1415/fp2/week6/camil/BinTree.icl new file mode 100644 index 0000000..0a16da5 --- /dev/null +++ b/1415/fp2/week6/camil/BinTree.icl @@ -0,0 +1,38 @@ +implementation module BinTree + +import StdEnv + +::  BTree a = BNode a (BTree a) (BTree a) | BLeaf + +t0 :: BTree Int +t0 = BLeaf +t1 :: BTree Int +t1 = BNode 4 t0 t0 +t2 :: BTree Int +t2 = BNode 2 t0 t1 +t3 :: BTree Int +t3 = BNode 5 t2 t0 +t4 :: BTree Int +t4 = BNode 5 t2 t2 +t5 :: BTree Int +t5 = BNode 1 BLeaf (BNode 2 BLeaf (BNode 3 BLeaf (BNode 4 BLeaf BLeaf))) +t6 :: BTree Int +t6 = BNode 1 (BNode 2 (BNode 3 (BNode 4 BLeaf BLeaf) BLeaf) BLeaf) BLeaf +t7 :: BTree Int +t7 = BNode 4 (BNode 1 BLeaf BLeaf) (BNode 5 (BNode 2 BLeaf BLeaf) BLeaf) + +//  2. +//nodes :: // meest algemene type +//nodes ... + +//Start = map nodes [t0,t1,t2,t3,t4,t5,t6,t7] + +//leaves :: // meest algemene type +//leaves ... + +//Start = map leaves [t0,t1,t2,t3,t4,t5,t6,t7] + +//diepte :: // meest algemene type +//diepte ... + +//Start = map diepte [t0,t1,t2,t3,t4,t5,t6,t7] diff --git a/1415/fp2/week6/mart/BinSearchTree.dcl b/1415/fp2/week6/mart/BinSearchTree.dcl new file mode 100755 index 0000000..460dcf1 --- /dev/null +++ b/1415/fp2/week6/mart/BinSearchTree.dcl @@ -0,0 +1,8 @@ +definition module BinSearchTree
 +
 +import StdClass
 +import BinTree
 +
 +is_geordend     :: (BTree a) -> Bool | Ord a // meest algemene type
 +is_gebalanceerd :: (BTree a) -> Bool | Ord a // meest algemene type
 +insertTree :: a (BTree a) -> BTree a | Ord a
\ No newline at end of file diff --git a/1415/fp2/week6/mart/BinSearchTree.icl b/1415/fp2/week6/mart/BinSearchTree.icl new file mode 100755 index 0000000..83ca73b --- /dev/null +++ b/1415/fp2/week6/mart/BinSearchTree.icl @@ -0,0 +1,49 @@ +// Mart Lubbers, s4109503 +// Camil Staps, s4498062 + +implementation module BinSearchTree + +import StdEnv +import BinTree + +insertTree :: a (BTree a) -> BTree a | Ord a +insertTree e BLeaf = BNode e BLeaf BLeaf +insertTree e (BNode x le ri) +| e <= x = BNode x (insertTree e le) ri +| e >  x = BNode x le (insertTree e ri) + +deleteTree :: a (BTree a) -> (BTree a) | Eq, Ord a +deleteTree e BLeaf = BLeaf +deleteTree e (BNode x le ri) +| e <  x = BNode x (deleteTree e le) ri +| e == x = join le ri +| e >  x = BNode x le (deleteTree e ri) +where +    join :: (BTree a) (BTree a) -> (BTree a) +    join BLeaf b2 = b2 +    join b1 b2 = BNode x b1` b2 +    where +        (x,b1`) = largest b1 +         +        largest :: (BTree a) -> (a,(BTree a)) +        largest (BNode x b1 BLeaf) = (x,b1) +        largest (BNode x b1 b2)   = (y,BNode x b1 b2`) +        where +            (y,b2`) = largest b2 + + +is_geordend :: (BTree a) -> Bool | Ord a // meest algemene type +is_geordend BLeaf = True +is_geordend (BNode x le ri) = (foldr (&&) True (map ((>) x) (members le))) && (foldr (&&) True (map ((<=) x) (members ri))) && is_geordend le && is_geordend ri +where +    members :: (BTree a) -> [a] +    members BLeaf = [] +    members (BNode x le ri) = [x:(members le) ++ (members ri)] + +is_gebalanceerd :: (BTree a) -> Bool | Ord a // meest algemene type +is_gebalanceerd BLeaf = True +is_gebalanceerd (BNode x le ri) = abs ((depth le) - (depth ri)) <= 1 && is_gebalanceerd le && is_gebalanceerd ri +where +    depth :: (BTree a) -> Int +    depth BLeaf = 0 +    depth (BNode x le ri) = max (depth le) (depth ri) + 1
\ No newline at end of file diff --git a/1415/fp2/week6/mart/BinSearchTreeImage.icl b/1415/fp2/week6/mart/BinSearchTreeImage.icl new file mode 100755 index 0000000..9b93810 --- /dev/null +++ b/1415/fp2/week6/mart/BinSearchTreeImage.icl @@ -0,0 +1,71 @@ +module BinSearchTreeImage
 +
 +/* Instructions:
 +
 +(1) copy BinTree.(i/d)cl and BinSearchTree.(i/d)cl from Practicum to
 +    {iTasks-SDK}\Experiments\SVG_tests\
 +    
 +(2) in these modules change the type
 +
 +    :: Tree a = Node a (Tree a) (Tree a) | Leaf
 +    
 +    to
 +    
 +    :: BTree a = BLeaf | BNode a (BTree a) (BTree a)	// ORDER OF DATACONSTRUCTORS IS ESSENTIAL!!
 +    
 +    and adapt the corresponding function definitions.
 +    
 +(3) this main file (BinSearchTreeImage.icl) must be in the same folder:
 +    {iTasks-SDK}\Experiments\SVG_tests\
 +    
 +(4) create a new project and set de environment to 'iTasks'
 +
 +(5) Bring-Up-To-Date and start generated application
 +
 +(6) Open a browser and navigate to localhost.
 +    The application creates two tasks:
 +    (a) The task on the left allows you to enter subsequent elements that are inserted in the tree, one after another.
 +    (b) The task on the right must be finished by you by writing the function treeImage. This function must render the tree structure in such a way
 +        that Nodes of the same depth have the same y-coordinate, and the root having the smallest y-coordinate.
 +*/
 +
 +import iTasks								// de algemene iTask API
 +import iTasks.API.Extensions.SVG.SVGlet		// specialiseer task editors
 +from   StdFunc import flip
 +
 +import BinSearchTree						// type definition of Tree and sample trees z0 .. z8
 +derive class iTask BTree
 +
 +Start				:: *World -> *World
 +Start world			= startEngine [publish "/" (WebApp []) (\_ -> task)] world
 +
 +task				:: Task [Int]
 +task				= withShared [] (\sharedList ->
 +						(  (updateSharedInformation (Title "Edit list") [] sharedList <<@ ArrangeHorizontal)
 +						   -||-
 +						   (viewSharedInformation (Title "Tree view") [imageView treeImage` (\_ _ -> Nothing)] sharedList <<@ ArrangeHorizontal)
 +						) <<@ ArrangeHorizontal
 +					  ) <<@ FullScreen
 +
 +font				= normalFontDef "Courier New" fonthoogte
 +fonthoogte			= 14.0
 +
 +treeImage`			:: [Int] *TagSource -> Image m
 +treeImage` nrs tags	= fst(treeImage (foldl (flip insertTree) BLeaf nrs) tags)
 +
 +TMargin = 10.0
 +
 +treeImage			:: (BTree Int) *TagSource -> (Image m, *TagSource)
 +treeImage BLeaf ts = (margin (px TMargin) (circle (px fonthoogte)), ts)
 +treeImage (BNode x t1 t2) [(tg1, utg1),(tg2, utg2):ts]
 += (above (repeat AtMiddleX) [] [textbox, lines, subtrees] Nothing, ts2)
 +	where
 +		(i1, ts1) = treeImage t1 ts
 +		(i2, ts2) = treeImage t2 ts1
 +		subtrees = beside (repeat AtTop) [] [tag utg1 i1, tag utg2 i2] Nothing
 +		box = rect (textxspan font (toString x)) (px fonthoogte) <@< {fill=toSVGColor "none"}
 +		textbox = overlay (repeat (AtMiddleX, AtMiddleY)) [] [box, text font (toString x)] Nothing
 +		lines = beside (repeat AtBottom) [] [
 +			line Nothing Slash ((imagexspan tg1) /. 2) (px TMargin),
 +			line Nothing Backslash ((imagexspan tg2) /. 2) (px TMargin)] Nothing
 +
 diff --git a/1415/fp2/week6/mart/BinTree.dcl b/1415/fp2/week6/mart/BinTree.dcl new file mode 100755 index 0000000..93d8ed8 --- /dev/null +++ b/1415/fp2/week6/mart/BinTree.dcl @@ -0,0 +1,16 @@ +definition module BinTree
 +
 +::  BTree a = BNode a (BTree a) (BTree a) | BLeaf
 +
 +t0 :: BTree Int
 +t1 :: BTree Int
 +t2 :: BTree Int
 +t3 :: BTree Int
 +t4 :: BTree Int
 +t5 :: BTree Int
 +t6 :: BTree Int
 +t7 :: BTree Int
 +
 +//nodes  :: // meest algemene type
 +//leaves :: // meest algemene type
 +//diepte :: // meest algemene type
 diff --git a/1415/fp2/week6/mart/BinTree.icl b/1415/fp2/week6/mart/BinTree.icl new file mode 100755 index 0000000..7b14e1e --- /dev/null +++ b/1415/fp2/week6/mart/BinTree.icl @@ -0,0 +1,38 @@ +implementation module BinTree
 +
 +import StdEnv
 +
 +::  BTree a = BNode a (BTree a) (BTree a) | BLeaf
 +
 +t0 :: BTree Int
 +t0 = BLeaf
 +t1 :: BTree Int
 +t1 = BNode 4 t0 t0
 +t2 :: BTree Int
 +t2 = BNode 2 t0 t1
 +t3 :: BTree Int
 +t3 = BNode 5 t2 t0
 +t4 :: BTree Int
 +t4 = BNode 5 t2 t2
 +t5 :: BTree Int
 +t5 = BNode 1 BLeaf (BNode 2 BLeaf (BNode 3 BLeaf (BNode 4 BLeaf BLeaf)))
 +t6 :: BTree Int
 +t6 = BNode 1 (BNode 2 (BNode 3 (BNode 4 BLeaf BLeaf) BLeaf) BLeaf) BLeaf
 +t7 :: BTree Int
 +t7 = BNode 4 (BNode 1 BLeaf BLeaf) (BNode 5 (BNode 2 BLeaf BLeaf) BLeaf)
 +
 +//  2.
 +//nodes :: // meest algemene type
 +//nodes ...
 +
 +//Start = map nodes [t0,t1,t2,t3,t4,t5,t6,t7]
 +
 +//leaves :: // meest algemene type
 +//leaves ...
 +
 +//Start = map leaves [t0,t1,t2,t3,t4,t5,t6,t7]
 +
 +//diepte :: // meest algemene type
 +//diepte ...
 +
 +//Start = map diepte [t0,t1,t2,t3,t4,t5,t6,t7]
 | 
