Skip to content

Commit

Permalink
updated to use type apps
Browse files Browse the repository at this point in the history
  • Loading branch information
cpeikert committed Aug 8, 2018
1 parent 0438624 commit 75e44aa
Showing 1 changed file with 20 additions and 18 deletions.
38 changes: 20 additions & 18 deletions lol-apps/Crypto/Lol/Applications/KeyHomomorphicPRF.hs
Expand Up @@ -11,20 +11,22 @@ Portability : POSIX
Key-homomorphic PRF from <http://web.eecs.umich.edu/~cpeikert/pubs/kh-prf.pdf [BP14]>.
-}

{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

module Crypto.Lol.Applications.KeyHomomorphicPRF
( FBT(..), SFBT, SizeFBT, FBTC, singFBT
Expand Down Expand Up @@ -73,7 +75,7 @@ newtype PRFKey n a = Key { key :: Matrix a }
-- | Generate an @n@-dimensional secret key over @rq@.
genKey :: forall rq rnd n . (MonadRandom rnd, Random rq, Reflects n Int)
=> rnd (PRFKey n rq)
genKey = fmap Key $ randomMtx 1 $ proxy value (Proxy :: Proxy n)
genKey = fmap Key $ randomMtx 1 $ value @n

-- | PRF public parameters for an @n@-dimension secret key over @a@,
-- using a gadget indicated by @gad@.
Expand All @@ -85,8 +87,8 @@ data PRFParams n gad a = Params { a0 :: (Matrix a), a1 :: (Matrix a) }
genParams :: forall gad rq rnd n .
(MonadRandom rnd, Random rq, Reflects n Int, Gadget gad rq)
=> rnd (PRFParams n gad rq)
genParams = let len = length $ untag (gadget :: Tagged gad [rq])
n = proxy value (Proxy :: Proxy n)
genParams = let len = length $ gadget @gad @rq
n = value @n
in Params <$> (randomMtx n (n*len)) <*> (randomMtx n (n*len))

-- | A random matrix having a given number of rows and columns.
Expand Down Expand Up @@ -140,7 +142,7 @@ updateState' t p st x = case t of
str = updateState' r p (right' <$> st) xr
al = matrix $ root' stl
ar = matrix $ root' str
ar' = reduce <$> proxy (decomposeMatrix ar) (Proxy :: Proxy gad)
ar' = reduce <$> decomposeMatrix @gad ar
in I (BSM x (al*ar')) stl str

updateState :: Decompose gad rq
Expand Down

0 comments on commit 75e44aa

Please sign in to comment.