diff --git a/.github/workflows/generate-website.yml b/.github/workflows/generate-website.yml index 417abc8..c0cb08d 100644 --- a/.github/workflows/generate-website.yml +++ b/.github/workflows/generate-website.yml @@ -59,6 +59,9 @@ jobs: - name: Generate 101 run: Generate101 + - name: Generate News + run: GenerateNews + - name: Generate website run: Generate diff --git a/Generate.hs b/Generate.hs index ece2079..f5e6aeb 100644 --- a/Generate.hs +++ b/Generate.hs @@ -126,7 +126,7 @@ substitute template env = loop template [] let varNm = reverse varAcc in case lookup varNm env of Nothing -> loop cs acc - Just val -> loop cs (reverse val ++ acc) + Just val -> loop cs (reverse (substitute val env) ++ acc) getVar (c:cs) varAcc acc = getVar cs (c:varAcc) acc -- | Check the input string to determine if it starts with a header of diff --git a/GenerateNews.hs b/GenerateNews.hs new file mode 100644 index 0000000..1b7daff --- /dev/null +++ b/GenerateNews.hs @@ -0,0 +1,151 @@ +{-# LANGUAGE DeriveGeneric, OverloadedStrings #-} +module Main where + +import Prelude hiding (div) +import GHC.Generics +import Data.Yaml + +import Data.List +import Data.Maybe +import Data.Function + +-- import Data.ByteString.Lazy (ByteString) +-- import qualified Data.ByteString.Lazy as LBS +import qualified Data.ByteString as BS +import Data.Text (Text) +import qualified Data.Text as T + +import Control.Applicative + +import Network.HTTP.Client +import Network.HTTP.Client.TLS +import Network.HTTP.Types.Status + +import Data.Time +import Data.Time.Format + +import Text.Feed.Types +import Text.Feed.Import +import Text.Feed.Query + +import Html + +------------------------------------------------------------------------------ +-- number of days to cut off old news +oldCutoff :: Integer +oldCutoff = 365 * 5 +------------------------------------------------------------------------------ + + +data NewsDate + = OneDate Day + | DateRange Day Day + deriving (Show, Eq) + +startDate :: NewsDate -> Day +startDate (OneDate d) = d +startDate (DateRange s e) = s + +newsDateToHTML :: NewsDate -> HTML +newsDateToHTML (OneDate day) = formatTime defaultTimeLocale "%e %B %Y" day +newsDateToHTML (DateRange start end) = + let (sy, sm, sd) = toGregorian start + (ey, em, ed) = toGregorian end + wholeMonths = sd == 1 && ed == gregorianMonthLength ey em + in case (sy == ey, sm == em, sd == ed, wholeMonths) of + (True, True, True, _) -> newsDateToHTML (OneDate start) + (True, True, False, True) -> fmt "%B %Y" end + (True, True, False, False) -> fmt "%e" start ++ dash ++ fmt "%e %B %Y" end + (True, False, False, True) -> fmt "%B" start ++ dash ++ fmt "%B %Y" end + (True, False, False, False) -> fmt "%e %B" start ++ dash ++ fmt "%e %B %Y" end + (_, _, _, True) -> fmt "%B %Y" start ++ dash ++ fmt "%B %Y" end + _ -> fmt "%e %B %Y" start ++ dash ++ fmt "%e %B %Y" end + where fmt = formatTime defaultTimeLocale + dash = " – " + +instance Ord NewsDate where + compare = compare `on` startDate + +data News = News + { date :: NewsDate + , desc :: String + } + deriving (Show, Eq) + +instance FromJSON News where + parseJSON = withObject "News" $ \ v -> do + desc <- v .: "description" + date <- single v <|> range v + pure (News date desc) + where + single v = do + date <- v .: "date" >>= parseTimeM True defaultTimeLocale "%e %B %Y" + pure (OneDate date) + range v = do + start <- v .: "start" >>= parseTimeM True defaultTimeLocale "%e %B %Y" + end <- v .: "end" >>= parseTimeM True defaultTimeLocale "%e %B %Y" + pure (DateRange start end) + + +newsToHTML :: News -> HTML +newsToHTML n = ddt (newsDateToHTML (date n), desc n) + +generateNews :: FilePath -> IO (HTML -- current news + , [(Year, HTML)] -- old news, grouped by year + ) +generateNews file = do + now <- getCurrentTime + f <- BS.readFile file + case decodeEither' f of + Left err -> + error (show err) + Right news -> do + let (old, new) = partition (\ x -> date x < OneDate (addDays (-oldCutoff) (utctDay now))) news + let oldGrouped = groupBy (\ a b -> startYear a == startYear b) old + pure (dlist new, map (\ x -> (startYear (head x), dlist x)) oldGrouped) + where + startYear x = let (y,_,_) = toGregorian (startDate (date x)) in y + dlist [] = "" + dlist x = tag "dl" (unlines (map newsToHTML x)) + +------------------------------------------------------------------------------ +pubsRSS :: Request +pubsRSS = parseRequest_ "https://pureportal.strath.ac.uk/en/organisations/mathematically-structured-programming/publications/?format=rss" + +getPureRSS :: Int -- number of entries + -> IO [Item] +getPureRSS n = do + manager <- newManager tlsManagerSettings + res <- httpLbs pubsRSS manager + case statusIsSuccessful (responseStatus res) of + False -> pure [] + True -> do + case parseFeedSource (responseBody res) of + Nothing -> pure [] + Just feed -> pure $ take n $ reverse $ sortOn (getItemPublishDate :: Item -> Maybe (Maybe UTCTime)) (feedItems feed) + + +itemToHTML :: Item -> Maybe HTML +itemToHTML i = do + -- title <- T.unpack <$> getItemTitle i + -- link <- T.unpack <$> getItemLink i + -- title and link are included in the description + desc <- T.unpack <$> getItemDescription i + pure desc + +main :: IO () +main = do + + rss <- getPureRSS 5 + let header = "### default.html(section.news=current,headtags=)\n" + let items = catMaybes $ map itemToHTML rss + let pubs = if (null items) then "" else + div "recent-pubs" $ + (h2 "Recent MSP publications") ++ + (ulist items) ++ + p ("See the " ++ (anchor "https://pureportal.strath.ac.uk/en/organisations/mathematically-structured-programming" "MSP PURE page") ++ " for a full list of recent papers, grants, etc.") + (newNews, oldNews) <- generateNews "_news.yaml" + let news = h2 "News" ++ newNews ++ if null oldNews then "" else h3 "Older News" ++ p ("See here for " ++ anchor "old-news.html" "older news" ++ ".") + let oldPage = h2 "Older news" ++ concatMap (\ (y, ds) -> h3 (show y) ++ ds) oldNews + writeFile "news.html" (header ++ pubs ++ news) + if null oldNews then pure () else writeFile "old-news.html" (header ++ oldPage) diff --git a/GeneratePeople.hs b/GeneratePeople.hs index d7c804f..d834005 100644 --- a/GeneratePeople.hs +++ b/GeneratePeople.hs @@ -6,6 +6,8 @@ import GHC.Generics import Data.Yaml import qualified Data.ByteString as BS +import Html + type Markdown = String data Status = Academic | PhDStudent | Research | PhDFinished | Alum @@ -22,15 +24,14 @@ instance FromJSON Status where data LinkRelationship = HomePage - | Staff | Pure | Thesis - | Uni + | Staff deriving (Show, Eq, Generic) instance FromJSON LinkRelationship where parseJSON (String "homepage") = pure HomePage - parseJSON (String "uni") = pure Uni + parseJSON (String "staff") = pure Staff parseJSON (String "pure") = pure Pure parseJSON (String "thesis") = pure Thesis parseJSON _ = fail "invalid link type" @@ -61,38 +62,14 @@ data Person = Person instance FromJSON Person ------------------------------------------------------------------------------ -type HTML = String - -div :: String -> HTML -> HTML -div klass content = - "
" ++ content ++ "
" - -ulist :: [HTML] -> HTML -ulist items = "James Brotherston visiting and giving a talk in the Departmental seminar at 3pm in room LT14.15 about Parametric completeness for separation theories (via hybrid logic).
+Abstract: In this talk, we consider the logical gap between the following two concepts:
+(1) provability in a propositional axiomatisation of separation logic, which is usually given by the bunched logic BBI; and
+(2) validity in an intended class of models of separation logic, as commonly considered in its program verification applications. Such intended classes are usually specified by a collection of algebraic axioms describing specific model properties, which we call a separation theory.
+Here, we show first that several typical properties of separation theories are in fact not definable in BBI. Then, we show that these properties become definable in a natural hybrid extension of BBI, obtained by adding a theory of naming to BBI in the same way that hybrid logic extends normal modal logic. Finally, we show how to build an axiomatic proof system for our hybrid logic in such a way that adding any axiom of a certain form yields a sound and complete proof system with respect to the models satisfying those axioms. In particular, this yields sound and complete proof systems for any separation theory from our considered class (which, to the best of our knowledge, includes all those appearing in the literature).
+This is joint work with Jules Villard, now at Imperial.
+ + +- date: 9 April 2014 + description: ++ David Aspinall visiting and giving a talk in the Departmental seminar about Managing Proofs Hierarchically. +
++ Abstract: For the past several years, we have + been studying the notion of hiproofs as a foundation for proof objects + with hierarchical structure. The idea is that a theorem proving tool + produces an internal representation that can be inspected, navigated + and manipulated as a hiproof. I'll give a review of the syntactic and + denotational formulations of hiproof, and the proof and manipulation + languages we have designed on top. I'll describe upcoming work which + will build on this, including the new ProofPeer project on + collaborative theorem proving. +
+ + +- date: 7 April 2014 + description: + Jamie Gabbay visiting. + +- start: 31 March 2014 + end: 4 April 2014 + description: + Thorsten Altenkirch visiting. + +- date: 16 August 2013 + description: + Dr Robin Adams will be joining the + MSP group as an Academic Visitor for the academic year + 2013-2014. Robin will (probably) be working on logic enriched type + theory, but I'm sure we will have plenty of other points of intersection. + + +- date: 12 August 2013 + description: + Neil Ghani has been awarded a SICSA Distinguished + Fellowship to host Andy Gill in October/November 2013 for two weeks. Andy will + be giving a number of lectures around Scotland on Domain Specific Languages + so let us know if you are interested in attending them. + +- date: 4 August 2013 + description: + The MSP group, as part of a consortium + of research groups, has been awarded an EU-travel grant to make + multiple visits to CMU (Steve Awodey and Bob Harper) in the US and + ANU (Dirk Pattinson) in Australia over the period 2014-2017. Time to + pack our bags! + +- date: 29 July 2013 + description: + + We are currently looking for a new + Lecturer or Senior Lecturer within the MSP group. See the + above link for how to apply (deadline is 8 September + 2013). Ideally we are looking for someone who ++ Applications are invited for lectureship within the MSP group at + the University of Strathclyde The applicant's motivation must + centre on a desire to discover beautiful mathematics of lasting + value. The applicant should also have an innate sense of the + wonder of learning allied with the capacity for self-motivation + and a track record of academic achievement. + +
+ The Mathematically Structured Programming Group's vision is to + use mathematics to understand the nature of computation, and to + then turn that understanding into practical advances within + programming languages research. This reflects the symbiotic + relationship between mathematics, programming, and the design of + programming languages --- we believe that any attempt to sever + this connection will diminish each component. In order to + achieve these research goals, we mainly use ideas from category + theory, type theory, and functional programming. The group + consists of a number of internationally leading researchers + including Professor Neil Ghani, Dr Patricia Johann, Dr Conor + McBride, Dr Peter Hancock, Dr Robert Atkey, and our PhD + students. + +
+ While the lectureship is formally in the area of Program + Verification, this is to be interpreted broadly. Very + broadly. Anyone interested should in the first instance contact + Professor Neil Ghani, whose email address is "neil.ghani at + strath.ac.uk" to register interest. Details of the position can + be found + at http://www.mis.strath.ac.uk/Personnel/open/712012.pdf. + +
+ The closing date for applications is Thursday July 26. + + +- date: 15 June 2012 + description: + "Upcoming event: International Workshop on 75 Years of the λ-Calculus" + + +- date: 1 June 2012 + description: + Congratulations to Clement Fumex on passing his + viva! Clement's thesis is entitled "Induction and Coinduction + schemes in Category Theory". His examiners + were Bart Jacobs + (external) and + Conor + McBride (internal). Clement's thesis was supervised by Patty + Johann. + + +- date: 25 May 2012 + description: + "Upcoming event: 6th Scottish Category Theory Seminar." + +- date: 2 May 2012 + description: + "Event Parametricity Workshop." + + +- date: 7 March 2012 + description: + "PhD Position: Higher Dimensional Categories and Types
Applications are invited for PhD study under the supervision of Prof Neil Ghani on any topic relating to higher dimensional category theory and/or higher dimensional type theory. The position is fully funded for EU students (apologies to non EU-citizens for this ridiculous piece of non-meritocracy) and will last for 3 years.The applicant's motivation must centre on a desire for beautiful mathematics of lasting value. The applicant should also have an innate sense of the wonder of learning allied to the capacity to work hard and achieve their goals.
The Mathematically Structured Programming Group's vision is to use mathematics to understand the nature of computation, and to then turn that understanding into the next generation of programming languages. This reflects the symbiotic relationship between mathematics, programming, and the design of programming languages — any attempt to sever this connection will diminish each component. In order to achieve these research goals we mainly use ideas from category theory, type theory and functional programming. Besides Professor Neil Ghani, the group consists of a number of internationally leading researchers including Dr Patricia Johann, Dr Conor McBride, Dr Peter Hancock, Dr Robert Atkey as well as a number of PhD students.
Anyone interested should in the first instance contact Professor Neil Ghani whose email address is "ng at cis.strath.ac.uk" and outline their academic background. Applications will be considered on a first come, first served basis.
" + + +- date: 10 February 2012 + description: + Scottish Theorem Provers Meeting + +- date: 19 December 2011 + description: + Peter Hancock at 60 + ++ We had a day of talks to celebrate Peter Hancock's 60th Birthday. + +
+ More information. + + +- date: 25 November 2011 + description: + 5th Scottish Category Theory Seminar + + +- date: 16 August 2011 + description: + 6 Month Postdoc Position
Mathematically Structured Programming Group
University of Strathclyde
Scotland
We have the potential to apply for funds for a 6 month post doctoral position. The idea is that the successful candidate would spend those 6 months writing a full scale grant to fund themselves for the next 3 years.
The postdoctoral position would be within the Mathematically Structured Programing group at the University of Strathclyde whose research focusses on category theory, type theory and functional programming. Current staff include Neil Ghani, Patricia Johann, Conor McBride, Peter Hancock, Robert Atkey and 6 PhD students.
The candidate we are looking for should be highly self motivated and appreciate that without beauty, we are lost.
Unfortunately, the deadline is extremely short and so any interested candidates should contact me immediately. I can then tell you more about what we would need to do.
For more information, please contact
Professor Neil Ghani
ng@cis.strath.ac.uk
http://personal.cis.strath.ac.uk/~ng/
http://msp.cis.strath.ac.uk/
+
+
+- date: 4 August 2011
+ description:
+ "Prakash Panangaden talk. 2pm.
Title: The Duality of State and Observation
Abstract: In this talk we consider the problem of representing and reasoning about systems, especially probabilistic systems, with hidden state. We consider transition systems where the state is not completely visible to an outside observer. Instead, there are observables that partly identify the state. We show that one can interchange the notions of state and observation and obtain what we call a dual system. The double dual gives a minimal representation of the behaviour of the original system. We extend this to nondeterministic systems and to probabilistic transition systems and finally to partially observable Markov decision processes (POMDPs). In the case of finite automata restricted to one observable, we obtain Brzozowski's algorithm for minimizing finite-state language acceptors. This is joint work with colleagues from McGill: Doina Precup and Joelle Pineau and my former student Chris Hunt.
" + + +- start: 1 June 2011 + end: 2 June 2011 + description: + Bart Jacobs visited. + + +- date: 17 May 2011 + description: + "Phil Scott talk.Title: Traced categories: algebraic structure of feedback and partial feedback in networks
Abstract: In the late '80s/early '90s an algebraic structure dealing with cyclic operations emerged from various fields, including flowchart schemes, dataflow networks with feedback, action calculi, proof theory, as well as algebraic topology and knot theory. This structure is now known as a "traced monoidal category", after the influential paper of Joyal, Street and Verity, who studied such categories in pure mathematics, but with an eye to applications in many fields. The concept also occurs as a basic structure in network algebra. Since then, these categories have been studied, with variations, in many areas of mathematics, logic and theoretical computer science, Recently, there has been a trend to consider partial traces and trace ideals; indeed it appears that such algebraic structures may be relevant to several areas, including biology and physics, or indeed to any field where cyclic networks are used. We give an introduction to the subject, along with some recent advances." + + +- date: 13 May 2011 + description: + 4th Scottish Category Theory Seminar + + +- start: 21 April 2011 + end: 25 April 2011 + description: + Janis Voigtländer visited. + + +- date: 17 February 2011 + description: + Nicola Gambino talk. 12pm. Location 14.15. + +
+ Title: Voevodsky's Univalence Axiom + +
+ Abstract: Vladimir Voevodsky has recently introduced a + semantics for constructive type theory in which types are + interpreted as simplicial sets. This semantics validates not + only the usual rules for identity types but also an additional + rule, called the Univalence Axiom. The aim of the talk is to + explain the statement of the Univalence Axiom and outline + Voevodsky's proof that it implies a form of function + extensionality. + +- date: 3 December 2010 + description: + "Algebraic Set Theory Course: Benno van den Berg" + + +- date: 2 December 2010 + description: + 3rd Scottish Category Theory Seminar + + +- start: 22 November 2010 + end: 26 November 2010 + description: + Wouter Swierstra visiting. + + +- date: 24 November 2010 + description: + Scottish Programming Languages Seminar diff --git a/_templates/default.html b/_templates/default.html index 86017b4..3354868 100644 --- a/_templates/default.html +++ b/_templates/default.html @@ -8,7 +8,7 @@ - {{Headtags}} + {{headtags}}
diff --git a/css/pure.css b/css/pure.css new file mode 100644 index 0000000..0e548ae --- /dev/null +++ b/css/pure.css @@ -0,0 +1,34 @@ +:root { + --light-purple: #f1ebf9; +} + + +.recent-pubs h3.title { + border-bottom: none; + font-size: 100%; + margin-bottom: 1px; +} + +.recent-pubs p { + margin-top: 1px; +} + +.recent-pubs p.type { + font-size: 80%; +} + +/* We get some empty links from the RSS for some reason; make them not look like links */ +.recent-pubs a.link[href="#"] { + text-decoration: none; + cursor: default; +} + + +div.recent-pubs { + border-radius: 0.7em; + background: var(--light-purple); + padding: 1em; + padding-top: 0.1em; + margin-bottom: 1em; + min-width: 190px; +} diff --git a/news.html b/news.html deleted file mode 100644 index f61f7fc..0000000 --- a/news.html +++ /dev/null @@ -1,161 +0,0 @@ -### default.html(section.news=current) - -See also the MSP PURE page for a list of our recent papers, grants, etc.
- -See here for older news.
diff --git a/old-news.html b/old-news.html deleted file mode 100644 index 2e3295e..0000000 --- a/old-news.html +++ /dev/null @@ -1,762 +0,0 @@ -### default.html(section.news=current) - -- James - Brotherston visiting and giving a talk in the Departmental - seminar at 3pm in room LT14.15 about Parametric completeness - for separation theories (via hybrid logic). -
-- Abstract: In this talk, we consider the logical -gap between the following two concepts: -
--(1) provability in a propositional axiomatisation of separation logic, -which is usually given by the bunched logic BBI; and -
--(2) validity in an intended class of models of separation logic, as -commonly considered in its program verification applications. Such -intended classes are usually specified by a collection of algebraic -axioms describing specific model properties, which we call a separation -theory. -
--Here, we show first that several typical properties of separation -theories are in fact not definable in BBI. Then, we show that these -properties become definable in a natural hybrid extension of BBI, -obtained by adding a theory of naming to BBI in the same way that hybrid -logic extends normal modal logic. Finally, we show how to build an -axiomatic proof system for our hybrid logic in such a way that adding -any axiom of a certain form yields a sound and complete proof system -with respect to the models satisfying those axioms. In particular, this -yields sound and complete proof systems for any separation theory from -our considered class (which, to the best of our knowledge, includes all -those appearing in the literature). -
--This is joint work with Jules Villard, now at Imperial. -
-- David Aspinall visiting and giving a talk in the Departmental seminar about Managing Proofs Hierarchically. -
-- Abstract: For the past several years, we have -been studying the notion of hiproofs as a foundation for proof objects -with hierarchical structure. The idea is that a theorem proving tool -produces an internal representation that can be inspected, navigated -and manipulated as a hiproof. I'll give a review of the syntactic and -denotational formulations of hiproof, and the proof and manipulation -languages we have designed on top. I'll describe upcoming work which -will build on this, including the new ProofPeer project on -collaborative theorem proving. -
-- Applications are invited for lectureship within the MSP group at - the University of Strathclyde The applicant's motivation must - centre on a desire to discover beautiful mathematics of lasting - value. The applicant should also have an innate sense of the - wonder of learning allied with the capacity for self-motivation - and a track record of academic achievement. - -
- The Mathematically Structured Programming Group's vision is to - use mathematics to understand the nature of computation, and to - then turn that understanding into practical advances within - programming languages research. This reflects the symbiotic - relationship between mathematics, programming, and the design of - programming languages --- we believe that any attempt to sever - this connection will diminish each component. In order to - achieve these research goals, we mainly use ideas from category - theory, type theory, and functional programming. The group - consists of a number of internationally leading researchers - including Professor Neil Ghani, Dr Patricia Johann, Dr Conor - McBride, Dr Peter Hancock, Dr Robert Atkey, and our PhD - students. - -
- While the lectureship is formally in the area of Program - Verification, this is to be interpreted broadly. Very - broadly. Anyone interested should in the first instance contact - Professor Neil Ghani, whose email address is "neil.ghani at - strath.ac.uk" to register interest. Details of the position can - be found - at http://www.mis.strath.ac.uk/Personnel/open/712012.pdf. - -
- The closing date for applications is Thursday July 26. -
- Applications are invited for PhD study under the supervision of - Prof Neil Ghani on any topic relating to higher dimensional - category theory and/or higher dimensional type theory. The - position is fully funded for EU students (apologies to non - EU-citizens for this ridiculous piece of non-meritocracy) and - will last for 3 years.The applicant's motivation must centre on - a desire for beautiful mathematics of lasting value. The - applicant should also have an innate sense of the wonder of - learning allied to the capacity to work hard and achieve their - goals. - -
- The Mathematically Structured Programming Group's vision is to - use mathematics to understand the nature of computation, and to - then turn that understanding into the next generation of - programming languages. This reflects the symbiotic relationship - between mathematics, programming, and the design of programming - languages — any attempt to sever this connection will diminish - each component. In order to achieve these research goals we - mainly use ideas from category theory, type theory and - functional programming. Besides Professor Neil Ghani, the group - consists of a number of internationally leading researchers - including Dr Patricia Johann, Dr Conor McBride, Dr Peter - Hancock, Dr Robert Atkey as well as a number of PhD students. - -
- Anyone interested should in the first instance contact Professor - Neil Ghani whose email address is "ng at cis.strath.ac.uk" and - outline their academic background. Applications will be - considered on a first come, first served basis. -
- We had a day of talks to celebrate Peter Hancock's 60th Birthday. - -
- More information. -
- Mathematically Structured Programming Group
- University of Strathclyde
- Scotland
-
-
- We have the potential to apply for funds for a 6 month post - doctoral position. The idea is that the successful candidate - would spend those 6 months writing a full scale grant to fund - themselves for the next 3 years. - -
- The postdoctoral position would be within the Mathematically - Structured Programing group at the University of Strathclyde - whose research focusses on category theory, type theory and - functional programming. Current staff include Neil Ghani, - Patricia Johann, Conor McBride, Peter Hancock, Robert Atkey and - 6 PhD students. - -
- The candidate we are looking for should be highly self motivated - and appreciate that without beauty, we are lost. - -
- Unfortunately, the deadline is extremely short and so any - interested candidates should contact me immediately. I can then - tell you more about what we would need to do. - -
- For more information, please contact: - -
- Professor Neil Ghani
- ng@cis.strath.ac.uk
- http://personal.cis.strath.ac.uk/~ng/
- http://msp.cis.strath.ac.uk/
-
- Title: The Duality of State and Observation - -
- Abstract: In this talk we consider the problem of - representing and reasoning about systems, especially - probabilistic systems, with hidden state. We consider - transition systems where the state is not completely visible to - an outside observer. Instead, there are observables that partly - identify the state. We show that one can interchange the - notions of state and observation and obtain what we call a dual - system. The double dual gives a minimal representation of the - behaviour of the original system. We extend this to - nondeterministic systems and to probabilistic transition systems - and finally to partially observable Markov decision processes - (POMDPs). In the case of finite automata restricted to one - observable, we obtain Brzozowski's algorithm for minimizing - finite-state language acceptors. This is joint work with - colleagues from McGill: Doina Precup and Joelle Pineau and my - former student Chris Hunt. -
- Title: Traced categories: algebraic structure of feedback and partial feedback in networks - -
- Abstract: In the late '80s/early '90s an algebraic - structure dealing with cyclic operations emerged from various - fields, including flowchart schemes, dataflow networks with - feedback, action calculi, proof theory, as well as algebraic - topology and knot theory. This structure is now known as a - "traced monoidal category" , after the influential paper of - Joyal, Street and Verity, who studied such categories in pure - mathematics, but with an eye to applications in many fields. The - concept also occurs as a basic structure in network - algebra. Since then, these categories have been studied, with - variations, in many areas of mathematics, logic and theoretical - computer science, Recently, there has been a trend to consider - partial traces and trace ideals; indeed it appears that such - algebraic structures may be relevant to several areas, including - biology and physics, or indeed to any field where cyclic - networks are used. We give an introduction to the subject, along - with some recent advances. -
- Title: Voevodsky's Univalence Axiom - -
- Abstract: Vladimir Voevodsky has recently introduced a - semantics for constructive type theory in which types are - interpreted as simplicial sets. This semantics validates not - only the usual rules for identity types but also an additional - rule, called the Univalence Axiom. The aim of the talk is to - explain the statement of the Univalence Axiom and outline - Voevodsky's proof that it implies a form of function - extensionality. -