CS 380 Lab #6
Prof. Richard Eisenberg
Spring 2017
Vec
sConsulting the documentation on lists, come up with types and implementations for the translation of the following functions to work on Vec
s. There should be no lists in your code.
These are put in order of expected difficulty.
and
or
any
map
last
unzip
uncons
(no need to use Maybe
)init
insert
sort
(use insertion sort)null
(this can return an SBool
)length
(this can return an SNat
)stripPrefix
take
(this takes an SNat
)drop
(this takes an SNat
)replicate
(this takes an SNat
)Here are some starter definitions you might find helpful:
{-# LANGUAGE GADTs, TypeInType, StandaloneDeriving, TypeFamilies,
TypeOperators, ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wincomplete-patterns #-}
module Lab06 where -- rename as you please
import Data.Kind ( Type )
data Nat where
Zero :: Nat
Succ :: Nat -> Nat
data Vec :: Nat -> Type -> Type where
Nil :: Vec Zero a
(:>) :: a -> Vec n a -> Vec (Succ n) a
infixr 5 :>
deriving instance Show a => Show (Vec n a)
type family (a :: Nat) + (b :: Nat) :: Nat where
Zero + b = b
Succ a + b = Succ (a + b)
infixl 6 +
-- singleton Nat
data SNat :: Nat -> Type where
SZero :: SNat Zero
SSucc :: SNat n -> SNat (Succ n)
-- singleton Bool
data SBool :: Bool -> Type where
SFalse :: SBool False
STrue :: SBool True