Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
427 changes: 427 additions & 0 deletions gibbon-compiler/examples/movie-micro-service/Basics.hs

Large diffs are not rendered by default.

Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
module GenerateMovieLayout where
import Movies


gibbon_main =
let
test = mkMovieContent 'a'
_ = printPacked test
in ()
20 changes: 20 additions & 0 deletions gibbon-compiler/examples/movie-micro-service/clean.py
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
# modified based on clean.py from blog management
import os
import subprocess

gibbon_file_names = ["test","testInsertmovie", "testSearchMovie", "testDeleteMovie"]

# layouts = ["layout1", "layout2", "layout3", "layout4", "layout5", "layout6", "layout7", "layout8"]

print("Cleaning out the c files and binaries")

#Compilation phase
for file_name in gibbon_file_names:

filename_c = file_name + ".c"
filename_exe = file_name + ".exe"
gibbon_cmd_c = subprocess.run(["rm", filename_c])
gibbon_cmd_bin = subprocess.run(["rm", filename_exe])
gibbon_cmd_bin = subprocess.run(["rm", file_name])


190 changes: 190 additions & 0 deletions gibbon-compiler/examples/movie-micro-service/movies.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,190 @@
module Movies where
-- import Data.Map
import Gibbon.Prelude
import Gibbon.PList
import Gibbon.Vector
import Gibbon.Prim
import Basics
-- ​
type Text = Vector Char
-- ​
type IsMovie = Bool
type MovieTitle = Text
type ReleaseDate = Text
type Director = Text
type Writers = PList Text
type CastInfo = PList Text
type MovieTags = PList Text
type Rating = Int

-- --if IsMovie == True, the maybe values will exist
data Movie = Empty
| Movie MovieTitle
ReleaseDate Director Writers CastInfo
MovieTags Rating

data MovieTrie = Root
| MovieTrie (Maybe Char) (Maybe IsMovie) (Maybe Movie) (Maybe (PList MovieTrie)) deriving (Show)

-- intToVec :: Int -> (Vector Int)
-- intToVec i = let
-- remainder = mod i 10
-- quotient = div i 10
-- in if(quotient == 0) then singleton remainder
-- else append (intToVec quotient) (singleton remainder)
-- intToChar :: Int -> Char
-- intToChar i = case i of
-- 0 -> '0'
-- 1 -> '1'
-- 2 -> '2'
-- 3 -> '3'
-- 4 -> '4'
-- 5 -> '5'
-- 6 -> '6'
-- 7 -> '7'
-- 8 -> '8'
-- 9 -> '9'
-- intToText :: (Vector Int) -> Text
-- intToText i = if (length i == 1) then
-- movieToText :: Movie -> Text
-- movieToText m = case m of
-- Empty -> "empty Movie"
-- Movie c title date director wrriters castinfo movietags rating ->
mkMovieContent :: Text -> Movie
mkMovieContent t =
let
movietitle = t
rdate = (getRandomString 5)
director = (getRandomString 6)
writer = Cons (getRandomString 5) Nil
cast = Cons (getRandomString 5) Nil
movietag = Cons (getRandomString 5) Nil
rating = 5
in Movie movietitle rdate director writer cast movietag rating

--insert a movie into movieTrie
insertMovie :: Text -> (Maybe Char) -> Movie -> MovieTrie -> MovieTrie
insertMovie t c m mt =
if (length t == 0)
then case mt of
Root -> MovieTrie c (Just True) (Just m) Nothing
MovieTrie c ismovie movie cmovieTrie -> MovieTrie c (Just True) (Just m) cmovieTrie
else
case mt of
Root -> MovieTrie c (Just False) Nothing (Just (Cons (insertMovie (tail t) (Just (head t)) m Root) Nil))
MovieTrie c ismovie movie cmovieTrie -> MovieTrie c ismovie movie (Just (insert_Mhelper t m (fromMaybe Nil cmovieTrie)))

movieGetChar :: MovieTrie -> Maybe Char
movieGetChar mt = case mt of
Root -> Nothing
-- let _ = printsym (quote "nothing")
-- in Nothing
MovieTrie c ismovie movie lmt -> c
-- let _ = printchar (fromMaybe ' ' c)
-- in c

insert_Mhelper :: Text -> Movie -> (PList MovieTrie) -> (PList MovieTrie)
insert_Mhelper t m lmt =
case lmt of
Nil -> Cons (insertMovie (tail t) (Just (head t)) m Root) Nil
Cons x xs -> if (fromMaybe ' ' (movieGetChar x)) *==* head t then Cons (insertMovie (tail t) (Just (head t)) m x) xs
else Cons x (insert_Mhelper t m xs)

deleteMovie :: Text -> MovieTrie -> MovieTrie
deleteMovie t mt =
if (length t == 0)
then case mt of
Root -> mt
MovieTrie c ismovie movie cmovieTrie -> if (fromMaybe False ismovie) then MovieTrie c (Just False) (Nothing) cmovieTrie
else MovieTrie c ismovie movie cmovieTrie
else
case mt of
Root -> Root
MovieTrie c ismovie movie cmovieTrie -> MovieTrie c ismovie movie (Just (delete_Mhelper t (fromMaybe Nil cmovieTrie)))


delete_Mhelper :: Text -> (PList MovieTrie) -> (PList MovieTrie)
delete_Mhelper t lmt =
case lmt of
Nil -> Nil
Cons x xs -> if(fromMaybe ' ' (movieGetChar x)) *==* head t then Cons (deleteMovie (tail t) x) xs
else Cons x (delete_Mhelper t xs)
--given movietitle, find movie return empty if not found
searchMovieTitle :: Text -> MovieTrie -> Movie
searchMovieTitle t mt =
if (length t == 0) then case mt of
Root -> Empty
MovieTrie c ismovie movie cmovieTrie -> if (fromMaybe False ismovie) then (fromMaybe Empty movie) else Empty
else
case mt of
Root -> Empty
MovieTrie c ismovie movie cmovieTrie -> if (isNothing cmovieTrie) then Empty
else
let
a = fromMaybe Nil cmovieTrie
in
case a of
Nil -> Empty
Cons x xs -> search_Mhelper t (Cons x xs)

search_Mhelper :: Text -> (PList MovieTrie) -> Movie
search_Mhelper t lmt =
case lmt of
Nil -> Empty
Cons x xs -> if (fromMaybe ' ' (movieGetChar x)) *==* (head t)
then searchMovieTitle (tail t) x
else search_Mhelper t xs

-- searchMovieRating :: Int -> MovieTrie ->(PList Movie) -> (PList Movie)
-- searchMovieTitle i mt lm =
-- case mt of
-- Root -> Nil
-- MovieTrie c ismovie movie cmovieTrie ->
-- let
-- rating = getMovieRating (fromMaybe Empty movie)
-- in if (rating > i) then Cons (fromMaybe Empty movie) (Search_MRhelper i cmovieTrie )
-- else Search_MRhelper i cmovieTrie

-- search_MRhelper :: Int -> (PList MovieTrie) -> (PList Movie) -> (PList Movie)

-- getMovieRating :: Movie -> Int
-- getMovieRating m = case m of
-- Empty -> 0
-- Movie movietitle releasedate director writers casinfo movitags rating -> rating

-- generateNode :: Char -> MovieTrie -> MovieTrie
-- generateNode a mt =
-- insertMovie :: Text -> MovieTrie -> MovieTrie
-- insertMovie title mt =
-- if isEmpty title then mt
-- else if mt == End then
-- let
-- a = head title
-- b = tail title
-- curNode = MovieTrie Nothing (singleton a) insertMovie b End
-- in curNode

isEmptyM :: Movie -> Bool
isEmptyM m = case m of
Empty -> True
Movie _ _ _ _ _ _ _ ->False

genMovieList :: Int -> (PList Text)
genMovieList i =
if (i == 0)
then Nil
else
let
a = mod rand 10
t = getRandomString a
nt = genMovieList (i - 1)
in Cons t nt

consMovieTrie :: (PList Text) -> MovieTrie ->MovieTrie
consMovieTrie lt mt =
case lt of
Nil -> mt
Cons x xs ->
let
movieContent = mkMovieContent x
in consMovieTrie xs (insertMovie x Nothing movieContent mt)
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
#t
19 changes: 19 additions & 0 deletions gibbon-compiler/examples/movie-micro-service/searchMovie.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
import Movies

type Text = Vector Char

getTitle :: Movie -> Text
getTitle m = case m of
Empty -> " "
Movie mt rd d w ci movietags rating -> mt

gibbon_main =
let
movielist = genMovieList 100
movie1 = fromMaybe " " (nth_plist movielist Nothing 10 )
len1 = vlength movie1
mt = consMovieTrie movielist Root
mv = searchMovieTitle movie1 mt
foundmovie = getTitle mv
len2 = vlength foundmovie
in len1 ==len2
9 changes: 9 additions & 0 deletions gibbon-compiler/examples/movie-micro-service/sth.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
import Gibbon.Prelude
import Gibbon.PList
import Gibbon.Vector
-- import Gibbon.Prim
gibbon_main = let
-- a = fromMaybe 10 (Nothing)
a = 10
_ = printint a
in ()
69 changes: 69 additions & 0 deletions gibbon-compiler/examples/movie-micro-service/test.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,69 @@
import Movies
-- data Ttext = Ttext (Vector Char)
printMovieTrie :: MovieTrie -> ()
printMovieTrie mt = case mt of
Root -> printsym (quote "nothing")
MovieTrie ch ismovie movie lmt -> if (isNothing ch) then
let
_ = printsym (quote "/")
in if (isNothing lmt) then ()
else print_MThelper (fromMaybe Nil lmt)
else let
a = fromMaybe ' ' ch
_ = printchar a
in if (isNothing lmt) then ()
else print_MThelper (fromMaybe Nil lmt)
print_MThelper :: (PList MovieTrie)->()
print_MThelper lmt = case lmt of
Nil -> ()
Cons x xs -> case x of
Root -> print_MThelper xs
MovieTrie ch ismovie movie lmt -> let
_ = printchar (fromMaybe ' ' ch)
_ = print_MThelper (fromMaybe Nil lmt)
in print_MThelper xs

gibbon_main =
-- let
-- -- testMovie = Movie 'a' "MovieTitle" "ReleaseDate"
-- -- testMovie = Empty
-- ttext = Ttext "fsaf"
-- -- testMovieTrie = MovieTrie (Just testMovie) (Just "Word") (Nothing)
-- -- testMovieTrie = MovieTrie testMovie
-- -- _ = printPacked testMovie

-- _ = printsym (quote "NEWLINE")
-- _ = printPacked ttext
-- -- _ = printsym (quote "NEWLINE")
-- in ()
-- putStrLn getRandomString 13
let
ri = mod rand 10
ri2 = mod rand 10
_ = printint ri2
_ = printint ri
-- smovie = mkMovieContent "titan"
-- movieT = insertMovie "titan" Nothing smovie Root
-- _ = printsym (quote " ")
-- _ = printMovieTrie movieT
-- movieT = insertMovie "titen" Nothing smovie movieT
-- _ = printsym (quote " ")
-- _ = printMovieTrie movieT
-- _ = printsym (quote "test")
-- mc = iterate (searchMovieTitle "tit" movieT)
-- movieT = deleteMovie "titan" movieT
-- _ = printsym (quote " ")
-- _ = printMovieTrie movieT

-- _ = printPacked mc
-- _ = printPacked movieT
-- let
-- _ = case movieT of
-- Empty -> printsym (quote "empty")
-- MovieTrie _ _ _ _ _ _ ->printsym (quote "valid")
-- in (
-- _ = printMovieTrie movieT
-- _ = if isEmptyM mc then printsym(quote "notfound") else printsym (quote "found")
-- _ = printPacked
-- _ = printsym (quote "a")
in ()
16 changes: 16 additions & 0 deletions gibbon-compiler/examples/movie-micro-service/testDeleteMovie.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
import Movies

type Text = Vector Char

testDelete :: (PList Text) -> MovieTrie -> MovieTrie
testDelete lt mt =
case lt of
Nil -> Root
Cons x xs -> testDelete xs (deleteMovie x mt)

gibbon_main =
let
movielist = genMovieList 20
mt = consMovieTrie movielist Root
mt2 = iterate (testDelete movielist mt)
in ()
13 changes: 13 additions & 0 deletions gibbon-compiler/examples/movie-micro-service/testInsertmovie.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
import Movies

testInsert :: Int -> MovieTrie -> MovieTrie
testInsert i mt = if (i == 0) then mt
else
let
title = getRandomString (mod rand 10)
movieContent = mkMovieContent title
in testInsert (i-1) (insertMovie title Nothing movieContent mt)
gibbon_main =
let
mvt = iterate (testInsert 1000 Root)
in ()
16 changes: 16 additions & 0 deletions gibbon-compiler/examples/movie-micro-service/testSearchMovie.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
import Movies

type Text = Vector Char

getTitle :: Movie -> Text
getTitle m = case m of
Empty -> " "
Movie mt rd d w ci movietags rating -> mt

gibbon_main =
let
movielist = genMovieList 1000
movie1 = fromMaybe " " (nth_plist movielist Nothing 100)
mt = consMovieTrie movielist Root
mv = iterate (searchMovieTitle movie1 mt)
in ()
Loading
Loading