Skip to content

Commit

Permalink
More tests for ucsd-progsys#1904
Browse files Browse the repository at this point in the history
  • Loading branch information
Fizzixnerd committed Jan 6, 2022
1 parent 8aaceac commit 943cc45
Show file tree
Hide file tree
Showing 5 changed files with 52 additions and 2 deletions.
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-@ LIQUID "--exact-data-cons" @-}

module AutoliftedFields where
-- data decl in LH is missing and uses a LH-refined type alias incorrectly

module AutoliftedFields00 where

{-@ type Nat = { v : Int | v >= 0 } @-}
type Nat = Int
Expand Down
15 changes: 15 additions & 0 deletions tests/datacon/neg/AutoliftedFields01.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
{-@ LIQUID "--exact-data-cons" @-}

-- data decl in LH and Haskell do not match and the LH one is not a subtype

module AutoliftedFields01 where

{-@ type Nat = { v : Int | v >= 0 } @-}
type Nat = Int

{-@ data T = T { getT :: Float } @-}
data T = T { getT :: Nat }

{-@ f :: { t : T | getT t >= 1 } -> Nat @-}
f :: T -> Nat
f (T x) = x
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-@ LIQUID "--exact-data-cons" @-}

module AutoliftedFields where
-- data decl in LH is missing but uses a LH-refined type alias correctly

module AutoliftedFields00 where

{-@ type Nat = { v : Int | v >= 0 } @-}
type Nat = Int
Expand Down
16 changes: 16 additions & 0 deletions tests/datacon/pos/AutoliftedFields01.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
{-@ LIQUID "--exact-data-cons" @-}

-- data decl in LH and Haskell give different names to the fields, but use them
-- in valid ways.

module AutoliftedFields01 where

{-@ type Nat = { v : Int | v >= 0 } @-}
type Nat = Int

{-@ data T = T { getMyT :: Nat } @-}
data T = T { getT :: Nat }

{-@ f :: { t : T | getT t == getMyT t } -> Nat @-}
f :: T -> Nat
f (T x) = x
15 changes: 15 additions & 0 deletions tests/datacon/pos/AutoliftedFields02.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
{-@ LIQUID "--exact-data-cons" @-}

-- data decl in LH and Haskell do not match but the LH is a subtype

module AutoliftedFields02 where

{-@ type Nat = { v : Int | v >= 0 } @-}
type Nat = Int

{-@ data T = T { getT :: Nat } @-}
data T = T { getT :: Int }

{-@ f :: { t : T | getT t >= 0 } -> Nat @-}
f :: T -> Nat
f (T x) = x

0 comments on commit 943cc45

Please sign in to comment.