Skip to content
Open
Show file tree
Hide file tree
Changes from 2 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
23 changes: 10 additions & 13 deletions copilot-core/copilot-core.cabal
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
cabal-version: >=1.10
cabal-version: 2.2
name: copilot-core
version: 4.6
synopsis: An intermediate representation for Copilot.
Expand All @@ -14,7 +14,7 @@ description:

author: Frank Dedden, Lee Pike, Robin Morisset, Alwyn Goodloe,
Sebastian Niller, Nis Nordbyop Wegmann, Ivan Perez
license: BSD3
license: BSD-3-Clause
license-file: LICENSE
maintainer: Ivan Perez <ivan.perezdominguez@nasa.gov>
homepage: https://copilot-language.github.io
Expand All @@ -31,16 +31,18 @@ source-repository head
location: https://github.com/Copilot-Language/copilot.git
subdir: copilot-core

library

common base
default-language: Haskell2010

hs-source-dirs: src
default-extensions:
LambdaCase

ghc-options:
-Wall
-fno-warn-orphans
-Werror

library
import: base
hs-source-dirs: src
build-depends:
base >= 4.9 && < 5

Expand All @@ -54,6 +56,7 @@ library
Copilot.Core.Type.Array

test-suite unit-tests
import: base
type:
exitcode-stdio-1.0

Expand All @@ -77,9 +80,3 @@ test-suite unit-tests

hs-source-dirs:
tests

default-language:
Haskell2010

ghc-options:
-Wall
9 changes: 7 additions & 2 deletions copilot-core/src/Copilot/Core/Type.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
Expand Down Expand Up @@ -48,6 +49,7 @@ module Copilot.Core.Type
import Data.Char (isLower, isUpper, toLower)
import Data.Coerce (coerce)
import Data.Int (Int16, Int32, Int64, Int8)
import qualified Data.Kind as DK
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

If we make this change, we have to align the surrounding imports (the module names need to be aligned, and the symbols imported need to be aligned. I normally use stylish-haskell for that.

Copy link
Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

import Data.List (intercalate)
import Data.Proxy (Proxy (..))
import Data.Type.Equality as DE
Expand Down Expand Up @@ -139,7 +141,7 @@ instance {-# OVERLAPPABLE #-} (Typed t, Struct t) => Show t where
-- Note that both arrays and structs use dependently typed features. In the
-- former, the length of the array is part of the type. In the latter, the
-- names of the fields are part of the type.
data Type :: * -> * where
data Type :: DK.Type -> DK.Type where
Bool :: Type Bool
Int8 :: Type Int8
Int16 :: Type Int16
Expand All @@ -165,6 +167,7 @@ typeLength _ = fromIntegral $ natVal (Proxy :: Proxy n)
typeSize :: forall n t . KnownNat n => Type (Array n t) -> Int
typeSize ty@(Array ty'@(Array _)) = typeLength ty * typeSize ty'
typeSize ty@(Array _ ) = typeLength ty
typeSize ty = error $ "There is a bug in the type checker " ++ show ty

instance TestEquality Type where
testEquality Bool Bool = Just DE.Refl
Expand Down Expand Up @@ -286,7 +289,9 @@ instance Typed Double where

instance (Typeable t, Typed t, KnownNat n) => Typed (Array n t) where
typeOf = Array typeOf
simpleType (Array t) = SArray t
simpleType = \case
Array t -> SArray t
o -> error $ "There is a bug in the type checker " ++ show o

-- | A untyped type (no phantom type).
data UType = forall a . Typeable a => UType (Type a)
Expand Down
4 changes: 2 additions & 2 deletions copilot-core/src/Copilot/Core/Type/Array.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,12 +53,12 @@ arrayUpdate (Array []) _ _ = error errMsg
where
errMsg = "copilot-core: arrayUpdate: Attempt to update empty array"

arrayUpdate (Array (x:xs)) 0 y = Array (y:xs)
arrayUpdate (Array (_x:xs)) 0 y = Array (y:xs)
Copy link
Member

@ivanperez-keera ivanperez-keera Nov 18, 2025

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Can we just make it _?

Copy link
Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.


arrayUpdate (Array (x:xs)) n y =
arrayAppend x (arrayUpdate (Array xs) (n - 1) y)
where
-- | Append to an array while preserving length information at the type
-- level.
arrayAppend :: a -> Array (n - 1) a -> Array n a
arrayAppend x (Array xs) = Array (x:xs)
arrayAppend x' (Array xs') = Array (x':xs')
4 changes: 1 addition & 3 deletions copilot-core/tests/Test/Copilot/Core/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ module Test.Copilot.Core.Type where

-- External imports
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Maybe (isJust)
import Data.Proxy (Proxy (..))
import Data.Type.Equality (TestEquality (..), testEquality,
(:~:) (..))
Expand Down Expand Up @@ -136,8 +135,7 @@ testSimpleTypesEqualityTransitive =
-- | Test that each type is only equal to itself.
testSimpleTypesEqualityUniqueness :: Property
testSimpleTypesEqualityUniqueness =
forAllBlind (shuffle simpleTypes) $ \(t:ts) ->
notElem t ts
forAllBlind (shuffle simpleTypes) $ \case [] -> False; (t:ts) -> notElem t ts

-- | Simple types tested.
simpleTypes :: [SimpleType]
Expand Down
8 changes: 4 additions & 4 deletions copilot-core/tests/Test/Copilot/Core/Type/Array.hs
Original file line number Diff line number Diff line change
Expand Up @@ -141,13 +141,13 @@ testArrayUpdateWrong len =
testArrayMakeWrongLength :: forall n . KnownNat n => Proxy n -> Property
testArrayMakeWrongLength len =
expectFailure $
forAll wrongLength $ \length ->
forAll (xsInt64 length) $ \ls ->
forAll wrongLength $ \length' ->
forAll (xsInt64 length') $ \ls ->
let array' :: Array n Int64
array' = array ls
in arrayElems array' == ls
where
xsInt64 length = vectorOf length arbitrary
xsInt64 length' = vectorOf length' arbitrary
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Can we align the $? Also, an alternative, shorter name could be len.

Copy link
Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

expectedLength = fromIntegral (natVal len)
wrongLength = (expectedLength +) . getNonNegative <$> arbitrary

Expand All @@ -157,7 +157,7 @@ testArrayUpdateElems :: forall n . KnownNat n => Proxy n -> Property
testArrayUpdateElems len =
forAll xsInt64 $ \ls ->
forAll position $ \p ->
forAll xInt64 $ \v ->
forAll xInt64 $ \_v ->
let -- Original array
array' :: Array n Int64
array' = array ls
Expand Down