{-# LANGUAGE TemplateHaskell, RankNTypes, TypeFamilies, TypeOperators,DataKinds, ScopedTypeVariables, GADTs, PolyKinds #-}module ListNat whereimport Data.Singletons$(singletons [d|data Nat = Zero | Succ Nat deriving Eq|])-- in HEAD, these next two are defined in Data.Type.Equalitydata a :~: b whereRefl :: a :~: agcastWith :: (a :~: b) -> ((a ~ b) => r) -> rgcastWith Refl x = x-- functionality that subsumes this will be in the next release of singletonsreifyNatEq :: forall (m :: Nat) (n :: Nat). ((m :==: n) ~ True, SingI m, SingI n) => m :~: nreifyNatEq =case (sing :: Sing m, sing :: Sing n) of(SZero, SZero) -> Refl(SSucc (_ :: Sing m'), SSucc (_ :: Sing n')) ->gcastWith (reifyNatEq :: (m' :~: n')) Refl_ -> bugInGHC -- this is necessary to prevent a spurious warning from GHCdata family X (n::Nat) :: *data L (n::Nat) whereQ :: L (Succ n) -> X n -> L nE :: L nextract :: SingI n => L Zero -> X nextract = auxwhereaux :: forall m n. (SingI m, SingI n) => L m -> X naux list =case ((sing :: Sing m) %==% (sing :: Sing n), list) of(_, E) -> error "Desired element does not exist"(STrue, Q _ datum) -> gcastWith (reifyNatEq :: (m :~: n)) datum(SFalse, Q rest _) -> aux restupdate :: forall n. SingI n => L Zero -> (X n -> X n) -> L Zeroupdate list upd = aux listwhereaux :: forall m. SingI m => L m -> L maux list =case ((sing :: Sing m) %==% (sing :: Sing n), list) of(_, E) -> error "Desired element does not exist"(STrue, Q rest datum) -> gcastWith (reifyNatEq :: (m :~: n)) (Q rest (upd datum))(SFalse, Q rest datum) -> Q (aux rest) datum
Is it possible to write extract and update functions for L ?Hello everyone,I'm still trying to resolve my problem. I try to restate it in a simpler way.
import Data.Nat
data family X (n::Nat) :: *
data L (n::Nat) where
Q :: L (Succ n) -> X n -> L n
E :: L n
extract :: L Zero -> X n
extract = undefined
update :: L Zero -> (X n -> X n) -> L Zero
update = undefinedThanks for hints and helppaolino_______________________________________________2013/10/7 Paolino <paolo.veronelli@gmail.com>
Hello, I'm trying to use a type class to select an element from a list.I would like to have a String "CC" as a value for l10'.
{-# LANGUAGE MultiParamTypeClasses, GADTs,FlexibleInstances, DataKinds ,TypeFamilies, KindSignatures, FlexibleContexts, OverlappingInstances, StandaloneDeriving, UndecidableInstances #-}
import Data.Nat
import Data.Monoid
data family X (n::Nat) :: *
data L (n::Nat) where
Q :: (Monoid (X n), Show (X n)) => L (Succ n) -> X n -> L n
E :: Monoid (X n) => L n
deriving instance Show (L n)
data instance X n = String String
instance Monoid (X n) where
String x `mappend` String y = String $ x `mappend` y
mempty = String ""
deriving instance Show (X n)
class Compose n n' where
compose :: L n -> L n -> X n'
instance Compose n n where
compose (Q _ x) (Q _ y) = x `mappend` y
compose _ _ = mempty
instance Compose n n' where
compose (Q x _) (Q y _) = compose x y
compose _ _ = mempty
l0 :: L Zero
l0 = Q (Q E $ String "C") $ String "A"
l0' :: L Zero
l0' = Q (Q E $ String "C") $ String "B"
l10' :: X (Succ Zero)
l10' = compose l0 l0'
l00' :: X Zero
l00' = compose l0 l0'
{-
*Main> l00'
String "AB"
*Main> l10'
String ""
-}Thanks for help.paolino
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe