Skip to content

Commit

Permalink
Added needed data
Browse files Browse the repository at this point in the history
  • Loading branch information
Oleksandr-Zhabenko committed Sep 21, 2024
1 parent 252f5e1 commit 4b3f130
Show file tree
Hide file tree
Showing 41 changed files with 7,299 additions and 19 deletions.
48 changes: 48 additions & 0 deletions Aftovolio/Basis.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,48 @@
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- |
-- Module : Aftovolio.Basis
-- Copyright : (c) OleksandrZhabenko 2020-2023
-- License : MIT
-- Stability : Experimental
-- Maintainer : [email protected]
--
-- Simplified version of the @phonetic-languages-common@ and @phonetic-languages-general@ packages.
-- Uses less dependencies.

{-# LANGUAGE BangPatterns, FlexibleContexts #-}

module Aftovolio.Basis where

import GHC.Base

data Result t a b c = R {line :: !(t a), propertiesF :: !b, transPropertiesF :: !c} deriving Eq

instance (Ord (t a), Ord b, Ord c) => Ord (Result t a b c) where
compare x y
= case compare (transPropertiesF x) (transPropertiesF y) of
!EQ -> case compare (propertiesF x) (propertiesF y) of
!EQ -> compare (line x) (line y)
!z -> z
!z0 -> z0
{-# INLINE compare #-}

data FuncRep2 a b c = D { getAB :: (a -> b), getBC :: (b -> c) }

getAC :: FuncRep2 a b c -> (a -> c)
getAC (D f g) = g . f
{-# INLINE getAC #-}

data Result2 a b c = R2 {line2 :: !a, propertiesF2 :: !b, transPropertiesF2 :: !c} deriving Eq

instance (Ord a, Ord b, Ord c) => Ord (Result2 a b c) where
compare x y
= case compare (transPropertiesF2 x) (transPropertiesF2 y) of
!EQ -> case compare (propertiesF2 x) (propertiesF2 y) of
!EQ -> compare (line2 x) (line2 y)
!z -> z
!z0 -> z0
{-# INLINE compare #-}


56 changes: 56 additions & 0 deletions Aftovolio/Coeffs.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,56 @@
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- |
-- Module : Aftovolio.Coeffs
-- Copyright : (c) OleksandrZhabenko 2020-2023
-- License : MIT
-- Stability : Experimental
-- Maintainer : [email protected]
--
-- The coefficients functionality common for both phonetic-languages-simplified-examples-array and phonetic-languages-simplified-generalized-examples-array lines of AFTOVolio.

{-# LANGUAGE BangPatterns #-}

module Aftovolio.Coeffs (
-- * Newtype to work with
CoeffTwo(..)
, Coeffs2
, isEmpty
, isPair
, fstCF
, sndCF
, readCF
) where

import GHC.Base
import GHC.List
import Data.Maybe (isNothing,fromMaybe,fromJust)
import Text.Read (readMaybe)

data CoeffTwo a = CF0 | CF2 (Maybe a) (Maybe a) deriving (Eq)

isEmpty :: CoeffTwo a -> Bool
isEmpty CF0 = True
isEmpty _ = False

isPair :: CoeffTwo a -> Bool
isPair CF0 = False
isPair _ = True

fstCF :: CoeffTwo a -> Maybe a
fstCF (CF2 x _) = x
fstCF _ = Nothing

sndCF :: CoeffTwo a -> Maybe a
sndCF (CF2 _ y) = y
sndCF _ = Nothing

readCF :: String -> Coeffs2
readCF xs
| any (== '_') xs = let (!ys,!zs) = (\(ks,ts) -> (readMaybe ks::Maybe Double,readMaybe (drop 1 ts)::Maybe Double)) . break (== '_') $ xs in
if (isNothing ys && isNothing zs) then CF0 else CF2 ys zs
| otherwise = CF0

-- | A data type that is used to represent the coefficients of the rhythmicity functions as a one argument value.
type Coeffs2 = CoeffTwo Double
363 changes: 363 additions & 0 deletions Aftovolio/Constraints.hs

Large diffs are not rendered by default.

Loading

0 comments on commit 4b3f130

Please sign in to comment.